--- trunk/Sources/dyn3d/dynetat0.f 2015/06/23 15:14:20 151 +++ trunk/dyn3d/dynetat0.f 2018/07/12 14:49:20 276 @@ -1,6 +1,6 @@ module dynetat0_m - use dimens_m, only: iim, jjm + use dimensions, only: iim, jjm IMPLICIT NONE @@ -15,37 +15,37 @@ integer:: annee_ref = 1998 ! Annee de l'etat initial (avec 4 chiffres) - REAL clon ! longitude of the center of the zoom, in rad - real clat ! latitude of the center of the zoom, in rad + REAL, protected:: clon ! longitude of the center of the zoom, in rad + real, protected:: clat ! latitude of the center of the zoom, in rad - real grossismx, grossismy + real, protected:: grossismx, grossismy ! facteurs de grossissement du zoom, selon la longitude et la latitude ! = 2 si 2 fois, = 3 si 3 fois, etc. - real dzoomx, dzoomy + real, protected:: dzoomx, dzoomy ! extensions en longitude et latitude de la zone du zoom (fractions ! de la zone totale) - real taux, tauy + real, protected:: taux, tauy ! raideur de la transition de l'int\'erieur \`a l'ext\'erieur du zoom real rlatu(jjm + 1) - ! (latitudes of points of the "scalar" and "u" grid, in rad) + ! latitudes of points of the "scalar" and "u" grid, in rad real rlatv(jjm) - ! (latitudes of points of the "v" grid, in rad, in decreasing order) + ! latitudes of points of the "v" grid, in rad, in decreasing order real rlonu(iim + 1) ! longitudes of points of the "u" grid, in rad real rlonv(iim + 1) - ! (longitudes of points of the "scalar" and "v" grid, in rad) + ! longitudes of points of the "scalar" and "v" grid, in rad real xprimu(iim + 1), xprimv(iim + 1) - ! xprimu et xprimv sont respectivement les valeurs de dx / di aux - ! points u et v. + ! 2 pi / iim * (derivative of the longitudinal zoom function)(rlon[uv]) REAL xprimm025(iim + 1), xprimp025(iim + 1) REAL rlatu1(jjm), rlatu2(jjm), yprimu1(jjm), yprimu2(jjm) + REAL ang0, etot0, ptot0, ztot0, stot0 save @@ -59,9 +59,8 @@ use comconst, only: dtvr use conf_gcm_m, only: raz_date - use dimens_m, only: iim, jjm, llm, nqmx + use dimensions, only: iim, jjm, llm, nqmx use disvert_m, only: pa - use ener, only: etot0, ang0, ptot0, stot0, ztot0 use iniadvtrac_m, only: tname use netcdf, only: NF90_NOWRITE, NF90_NOERR use netcdf95, only: NF95_GET_VAR, nf95_open, nf95_inq_varid, NF95_CLOSE, & @@ -80,7 +79,7 @@ ! Local variables: INTEGER iq - REAL, pointer:: tab_cntrl(:) ! tableau des param\`etres du run + REAL, allocatable:: tab_cntrl(:) ! tableau des param\`etres du run INTEGER ierr, ncid, varid namelist /dynetat0_nml/ day_ref, annee_ref @@ -149,8 +148,6 @@ print *, "day_ini = ", day_ini - deallocate(tab_cntrl) ! pointer - call NF95_INQ_VARID (ncid, "rlonu", varid) call NF95_GET_VAR(ncid, varid, rlonu) @@ -187,7 +184,7 @@ CALL nf95_inq_varid(ncid, 'yprimu2', varid) CALL nf95_get_var(ncid, varid, yprimu2) - call NF95_INQ_VARID (ncid, "phisinit", varid) + call NF95_INQ_VARID (ncid, "phis", varid) call NF95_GET_VAR(ncid, varid, phis) call NF95_INQ_VARID (ncid, "ucov", varid) @@ -201,12 +198,12 @@ DO iq = 1, nqmx call NF95_INQ_VARID(ncid, tname(iq), varid, ierr) - IF (ierr /= NF90_NOERR) THEN + IF (ierr == NF90_NOERR) THEN + call NF95_GET_VAR(ncid, varid, q(:, :, :, iq)) + ELSE PRINT *, 'dynetat0: "' // tname(iq) // '" not found, ' // & "setting it to zero..." q(:, :, :, iq) = 0. - ELSE - call NF95_GET_VAR(ncid, varid, q(:, :, :, iq)) ENDIF ENDDO @@ -223,4 +220,39 @@ END SUBROUTINE dynetat0 + !******************************************************************** + + subroutine read_serre + + use unit_nml_m, only: unit_nml + use nr_util, only: assert, pi + + REAL:: clon_deg = 0. ! longitude of the center of the zoom, in degrees + real:: clat_deg = 0. ! latitude of the center of the zoom, in degrees + + namelist /serre_nml/ clon_deg, clat_deg, grossismx, grossismy, dzoomx, & + dzoomy, taux, tauy + + !------------------------------------------------- + + ! Default values: + grossismx = 1. + grossismy = 1. + dzoomx = 0.2 + dzoomy = 0.2 + taux = 3. + tauy = 3. + + print *, "Enter namelist 'serre_nml'." + read(unit=*, nml=serre_nml) + write(unit_nml, nml=serre_nml) + + call assert(grossismx >= 1. .and. grossismy >= 1., "read_serre grossism") + call assert(dzoomx > 0., dzoomx < 1., dzoomy < 1., & + "read_serre dzoomx dzoomy") + clon = clon_deg / 180. * pi + clat = clat_deg / 180. * pi + + end subroutine read_serre + end module dynetat0_m