--- trunk/libf/dyn3d/dynetat0.f90 2012/01/30 12:54:02 57 +++ trunk/dyn3d/dynetat0.f 2015/02/24 15:43:51 130 @@ -2,29 +2,38 @@ IMPLICIT NONE - INTEGER day_ini + INTEGER day_ini + ! day number at the beginning of the run, based at value 1 on + ! January 1st of annee_ref + + integer:: day_ref = 1 ! jour de l'année de l'état initial + ! (= 350 si 20 décembre par exemple) + + integer:: annee_ref = 1998 ! Annee de l'etat initial (avec 4 chiffres) contains - SUBROUTINE dynetat0(vcov, ucov, teta, q, masse, ps, phis, time_0) + SUBROUTINE dynetat0(vcov, ucov, teta, q, masse, ps, phis) ! From dynetat0.F, version 1.2, 2004/06/22 11:45:30 ! Authors: P. Le Van, L. Fairhead ! This procedure reads the initial state of the atmosphere. - use comconst, only: im, dtvr, jm, lllm - use comvert, only: pa + use comconst, only: dtvr use comgeom, only: rlonu, rlatu, rlonv, rlatv, cu_2d, cv_2d, aire_2d + use conf_gcm_m, only: raz_date use dimens_m, only: iim, jjm, llm, nqmx + use disvert_m, only: pa use ener, only: etot0, ang0, ptot0, stot0, ztot0 use iniadvtrac_m, only: tname - use conf_gcm_m, only: fxyhypb, ysinus - use serre, only: clon, clat, grossismy, grossismx + use netcdf, only: NF90_NOWRITE, NF90_NOERR use netcdf95, only: NF95_GET_VAR, nf95_open, nf95_inq_varid, NF95_CLOSE, & NF95_Gw_VAR - use netcdf, only: NF90_NOWRITE, NF90_NOERR use nr_util, only: assert - use temps, only: day_ref, itau_dyn, annee_ref + use serre, only: clon, clat, grossismy, grossismx, dzoomx, dzoomy, taux, & + tauy + use temps, only: itau_dyn + use unit_nml_m, only: unit_nml REAL, intent(out):: vcov(: , :, :) ! (iim + 1, jjm, llm) REAL, intent(out):: ucov(:, :, :) ! (iim + 1, jjm + 1, llm) @@ -33,13 +42,14 @@ REAL, intent(out):: masse(:, :, :) ! (iim + 1, jjm + 1, llm) REAL, intent(out):: ps(:, :) ! (iim + 1, jjm + 1) in Pa REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1) - REAL, intent(out):: time_0 ! Local variables: INTEGER iq REAL, pointer:: tab_cntrl(:) ! tableau des paramètres du run INTEGER ierr, ncid, varid + namelist /dynetat0_nml/ day_ref, annee_ref + !----------------------------------------------------------------------- print *, "Call sequence information: dynetat0" @@ -59,29 +69,52 @@ call nf95_inq_varid(ncid, "controle", varid) call NF95_Gw_VAR(ncid, varid, tab_cntrl) - im = int(tab_cntrl(1)) - jm = int(tab_cntrl(2)) - lllm = int(tab_cntrl(3)) - call assert(im == iim, "dynetat0 im iim") - call assert(jm == jjm, "dynetat0 jm jjm") - call assert(lllm == llm, "dynetat0 lllm llm") - - day_ref = int(tab_cntrl(4)) - annee_ref = int(tab_cntrl(5)) - dtvr = tab_cntrl(12) + call assert(int(tab_cntrl(1)) == iim, "dynetat0 tab_cntrl iim") + call assert(int(tab_cntrl(2)) == jjm, "dynetat0 tab_cntrl jjm") + call assert(int(tab_cntrl(3)) == llm, "dynetat0 tab_cntrl llm") + + IF (dtvr /= tab_cntrl(12)) THEN + print *, 'Warning: the time steps from day_step and "start.nc" ' // & + 'are different.' + print *, 'dtvr from day_step: ', dtvr + print *, 'dtvr from "start.nc": ', tab_cntrl(12) + print *, 'Using the value from day_step.' + ENDIF + etot0 = tab_cntrl(13) ptot0 = tab_cntrl(14) ztot0 = tab_cntrl(15) stot0 = tab_cntrl(16) ang0 = tab_cntrl(17) pa = tab_cntrl(18) + clon = tab_cntrl(20) clat = tab_cntrl(21) grossismx = tab_cntrl(22) grossismy = tab_cntrl(23) - fxyhypb = tab_cntrl(24) == 1. - if (.not. fxyhypb) ysinus = tab_cntrl(27) == 1. - itau_dyn = tab_cntrl(31) + dzoomx = tab_cntrl(25) + dzoomy = tab_cntrl(26) + taux = tab_cntrl(28) + tauy = tab_cntrl(29) + + print *, "Enter namelist 'dynetat0_nml'." + read(unit=*, nml=dynetat0_nml) + write(unit_nml, nml=dynetat0_nml) + + if (raz_date) then + print *, 'On réinitialise à la date lue dans la namelist.' + day_ini = day_ref + itau_dyn = 0 + else + day_ref = tab_cntrl(4) + annee_ref = tab_cntrl(5) + itau_dyn = tab_cntrl(31) + day_ini = tab_cntrl(30) + end if + + print *, "day_ini = ", day_ini + + deallocate(tab_cntrl) ! pointer call NF95_INQ_VARID (ncid, "rlonu", varid) call NF95_GET_VAR(ncid, varid, rlonu) @@ -107,15 +140,6 @@ call NF95_INQ_VARID (ncid, "phisinit", varid) call NF95_GET_VAR(ncid, varid, phis) - call NF95_INQ_VARID (ncid, "temps", varid) - call NF95_GET_VAR(ncid, varid, time_0) - - day_ini = tab_cntrl(30) + INT(time_0) - time_0 = time_0 - INT(time_0) - ! {0 <= time0 < 1} - - deallocate(tab_cntrl) ! pointer - call NF95_INQ_VARID (ncid, "ucov", varid) call NF95_GET_VAR(ncid, varid, ucov) @@ -141,6 +165,9 @@ call NF95_INQ_VARID (ncid, "ps", varid) call NF95_GET_VAR(ncid, varid, ps) + ! Check that there is a single value at each pole: + call assert(ps(1, 1) == ps(2:, 1), "dynetat0 ps north pole") + call assert(ps(1, jjm + 1) == ps(2:, jjm + 1), "dynetat0 ps south pole") call NF95_CLOSE(ncid)