Skip to content
Snippets Groups Projects
Commit 573bac4e authored by wactbprot's avatar wactbprot
Browse files

bug in uncert/se1.uncert_pressure_fill.r

parent d7f2a819
No related branches found
No related tags found
No related merge requests found
......@@ -17,11 +17,24 @@ se1.pressure.ind <- function(ccc){
if(!is.null(IND) & !is.null(OFF)){
cal <- getConstVal(NA, NA, CAL)
# Pa, Torr ...
if(IND$Unit != "DCR"){
ind <- getConstVal(NA, NA, IND) * getConvFactor(ccc, pUnit, IND$Unit)
off <- getConstVal(NA, NA, OFF) * getConvFactor(ccc, pUnit, OFF$Unit)
if(length(a$ccu$Setup) > 0 & length(a$ccu$Setup$Temperature) > 0) {
T.ref <- as.numeric(a$ccu$Setup$Temperature)
T.real <- getConstVal(a$cav, "after")
T.corr <- sqrt(T.real/T.ref)
ind <- ind * T.corr
off <- off * T.corr
}
}
## DCR
if(IND$Unit == "DCR" & OFF$Unit == "DCR"){
......
source("load.r")
cdb <- cdbIni()
cdb$id <- "cal-2017-se1-vg-4812_0005"
cdb$id <- "cal-2017-se1-kk-75093_0002"
cdb$DBName <- "vl_db"
doc <- cdbGetDoc(cdb)$res
......@@ -18,6 +18,7 @@ doc <- se1.real.gas.corr(doc)
doc <- se1.pressure.rise(doc)
doc <- se1.pressure.cal(doc)
doc <- se1.pressure.ind(doc)
if(length(a$ct) > 0){
resType <- a$ct$Type
if(resType == "sigma"){
......@@ -43,12 +44,12 @@ doc <- se1.uncertRep(doc)
doc <- se1.uncertPcal(doc)
s <- getConstVal(doc$Calibration$Analysis$Values$Sigma, "eff")
out <- which(abs(s) > 1.2)
s[out] <- NA
p <- getConstVal(doc$Calibration$Analysis$Values$Pressure, "cal")
u <- getConstVal(doc$Calibration$Analysis$Values$Uncertainty, "uncertPcal_rel")
e <- getConstVal(doc$Calibration$Analysis$Values$Error, "relative")
if(FALSE){
cdb$DBName <- "vl_db"
cdb$dataList <- doc
......@@ -66,23 +67,22 @@ if(FALSE){
# #dev.off()
#
#if(a$cs == "SE1" & a$cpt$Type == "srg_error"){
# doc <- cuco.uncertVisc(doc)
# doc <- cuco.uncertDigit(doc)
# doc <- cuco.uncertPOffset(doc)
# doc <- cuco.uncertOffsetDrift(doc)
# doc <- cuco.uncertExpSd(doc)
# doc <- cuco.uncertPrise(doc)
#}
#
#doc <- cuco.uncertPind(doc)
#
#doc <- se1.uncertTotal(doc)
#
#doc <- dispatchResCal(doc)
#doc <- dispatchResSum(doc)
#
#
#doc <- dispatchResCal(doc)
#
\ No newline at end of file
# if(a$cs == "SE1" & a$cpt$Type == "srg_error"){
# doc <- cuco.uncertVisc(doc)
# doc <- cuco.uncertDigit(doc)
# doc <- cuco.uncertPOffset(doc)
# doc <- cuco.uncertOffsetDrift(doc)
# doc <- cuco.uncertExpSd(doc)
# doc <- cuco.uncertPrise(doc)
# }
# #
# doc <- cuco.uncertPind(doc)
#
# doc <- se1.uncertTotal(doc)
#
# doc <- dispatchResCal(doc)
# doc <- dispatchResSum(doc)
# #
#
# doc <- dispatchResCal(doc)
......@@ -19,7 +19,7 @@ se1.uncertPfill <- function(ccc){
(pfill < as.numeric(RANGE.100$To)))
i.1000 <- which((pfill > as.numeric(RANGE.1000$From)) &
(pfill < as.numeric(RANGE.1000$To)))
## --- 10Torr CDG --- wie in QS 2/14 vorgegeben
if(length(i.10) > 0){
u1 <- getConstVal(a$cco, "cdg10_u1") ## rel.
......@@ -47,7 +47,8 @@ se1.uncertPfill <- function(ccc){
u1 <- rep(NA, length(pfill))
u1[iu1a] <- getConstVal(NA, NA, U1a)
u1[iu1b] <- getConstVal(NA, NA, U1b)
u1[iu1c] <- getConstVal(NA, NA, U1c)
u2 <- getConstVal(a$cco, "cdg100_u2")/pfill ## abs.
u4 <- getConstVal(a$cco, "cdg100_u4") ## rel.
u5 <- getConstVal(a$cco, "cdg100_u5") ## rel.
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment