Commit 7f41bec2 authored by François Bourgin's avatar François Bourgin Committed by fbourgin
Browse files

UPDATE: ETP Oudin daily for several locations

Showing with 12 additions and 8 deletions
+12 -8
......@@ -28,9 +28,9 @@ PEdaily_Oudin <- function(JD, Temp, LatRad, Lat, LatUnit = c("rad", "deg"), run_
if (!any(LatUnit %in% c("rad", "deg"))) {
stop("'LatUnit' must be one of \"rad\" or \"deg\"")
}
if (!inherits(Lat, "numeric") | length(Lat) != 1) {
stop("'Lat' must be a 'numeric' of length one")
}
# if (!inherits(Lat, "numeric") | length(Lat) != 1) {
# stop("'Lat' must be a 'numeric' of length one")
# }
if (LatUnit[1L] == "rad" & ((Lat >= pi/2) | (Lat <= -pi/2))) {
stop("'Lat' must be comprised between -pi/2 and +pi/2 degrees")
}
......@@ -55,12 +55,17 @@ PEdaily_Oudin <- function(JD, Temp, LatRad, Lat, LatUnit = c("rad", "deg"), run_
if (LatUnit[1L] == "rad") {
Lat = Lat * 180 / pi
}
LInputs = as.integer(length(Temp))
if (length(Lat) == 1) {
Lat = rep(Lat, LInputs)
}
RESULTS <- .Fortran("frun_etp_oudin", PACKAGE="airGR",
##inputs
LInputs = LInputs,
xLAT = as.double(Lat),
InputsLAT = as.double(Lat),
InputsTT = as.double(Temp),
InputsJJ = as.double(JD),
##outputs
......
!*******************************************************************************
SUBROUTINE frun_etp_oudin(LInputs,LAT,InputsTT,InputsJJ,OutputsETP)
SUBROUTINE frun_etp_oudin(LInputs,InputsLAT,InputsTT,InputsJJ,OutputsETP)
!*******************************************************************************
!DEC$ ATTRIBUTES DLLEXPORT :: frun_etp_oudin
......@@ -9,7 +9,7 @@
!! dummies
! in
integer, intent(in) :: LInputs
doubleprecision, intent(in) :: LAT
doubleprecision, dimension(LInputs), intent(in) :: InputsLAT
doubleprecision, dimension(LInputs), intent(in) :: InputsTT
doubleprecision, dimension(LInputs), intent(in) :: InputsJJ
......@@ -20,14 +20,13 @@
integer :: k
real :: FI, tt, jj, ETPoud
FI = LAT / 57.296
!--------------------------------------------------------------
! Time loop
!--------------------------------------------------------------
DO k=1,LInputs
tt = InputsTT(k)
jj = InputsJJ(k)
FI = InputsLAT(k) / 57.296
!model run on one time step
CALL ETP_OUDIN(FI,tt,jj,ETPoud)
!storage of outputs
......
Supports Markdown
0% or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment