diff --git a/R/PEdaily_Oudin.R b/R/PEdaily_Oudin.R index 7689fd5b22f3ccde884131cf3825b6df09cd5b60..c677966407f1255b33aa3d128c3d8d1d0f415034 100644 --- a/R/PEdaily_Oudin.R +++ b/R/PEdaily_Oudin.R @@ -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 diff --git a/src/frun_ETP.f90 b/src/frun_ETP.f90 index 2fbb5fdc47794cafc683f4b0ad42919b90df9758..c0c6f20ddf9dd5936066c43ab5b9ef34ae9e09d0 100644 --- a/src/frun_ETP.f90 +++ b/src/frun_ETP.f90 @@ -1,5 +1,5 @@ !******************************************************************************* - 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