--- trunk/dyn3d/etat0.f90 2014/02/28 17:52:47 79 +++ trunk/dyn3d/etat0.f 2014/07/02 18:39:15 99 @@ -15,7 +15,7 @@ SUBROUTINE etat0 - ! From "etat0_netcdf.F", version 1.3 2005/05/25 13:10:09 + ! From "etat0_netcdf.F", version 1.3, 2005/05/25 13:10:09 use caldyn0_m, only: caldyn0 use comconst, only: cpp, kappa, iniconst @@ -40,10 +40,9 @@ use netcdf, only: nf90_nowrite use netcdf95, only: nf95_close, nf95_get_var, nf95_gw_var, & nf95_inq_varid, nf95_open - use nr_util, only: pi + use nr_util, only: pi, assert use paramet_m, only: ip1jm, ip1jmp1 use phyredem_m, only: phyredem - use pressure_var, only: pls, p3d use q_sat_m, only: q_sat use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz use regr_pr_o3_m, only: regr_pr_o3 @@ -53,12 +52,13 @@ use start_init_phys_m, only: start_init_phys use start_inter_3d_m, only: start_inter_3d use temps, only: itau_phy, annee_ref, day_ref + use test_disvert_m, only: test_disvert ! Variables local to the procedure: REAL latfi(klon), lonfi(klon) ! (latitude and longitude of a point of the scalar grid identified - ! by a simple index, in °) + ! by a simple index, in degrees) REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta REAL vcov(iim + 1, jjm, llm) @@ -69,15 +69,14 @@ ! and pressure level "pls(i, j, l)".) real qsat(iim + 1, jjm + 1, llm) ! mass fraction of saturating water vapor - REAL tsol(klon), qsol(klon), sn(klon) - REAL tsolsrf(klon, nbsrf), qsolsrf(klon, nbsrf), snsrf(klon, nbsrf) + REAL sn(klon) + REAL qsolsrf(klon, nbsrf), snsrf(klon, nbsrf) REAL albe(klon, nbsrf), evap(klon, nbsrf) REAL alblw(klon, nbsrf) REAL tsoil(klon, nsoilmx, nbsrf) REAL radsol(klon), rain_fall(klon), snow_fall(klon) REAL solsw(klon), sollw(klon), fder(klon) !IM "slab" ocean - REAL tslab(klon) real seaice(klon) ! kg m-2 REAL frugs(klon, nbsrf), agesno(klon, nbsrf) REAL rugmer(klon) @@ -93,7 +92,7 @@ REAL run_off_lic_0(klon) real clwcon(klon, llm), rnebcon(klon, llm), ratqs(klon, llm) - ! Déclarations pour lecture glace de mer : + ! D\'eclarations pour lecture glace de mer : INTEGER iml_lic, jml_lic INTEGER ncid, varid REAL, pointer:: dlon_lic(:), dlat_lic(:) @@ -108,11 +107,20 @@ REAL masse(iim + 1, jjm + 1, llm) REAL phi(iim + 1, jjm + 1, llm) REAL pbaru(ip1jmp1, llm), pbarv(ip1jm, llm) - REAL w(ip1jmp1, llm) + REAL w(iim + 1, jjm + 1, llm) real sig1(klon, llm) ! section adiabatic updraft real w01(klon, llm) ! vertical velocity within adiabatic updraft + real pls(iim + 1, jjm + 1, llm) + ! (pressure at mid-layer of LMDZ grid, in Pa) + ! "pls(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)", + ! for layer "l") + + REAL p3d(iim + 1, jjm + 1, llm+1) ! pressure at layer interfaces, in Pa + ! ("p3d(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)", + ! for interface "l") + !--------------------------------- print *, "Call sequence information: etat0" @@ -123,6 +131,7 @@ pa = 5e4 CALL disvert + call test_disvert CALL inigeom CALL inifilr @@ -148,10 +157,7 @@ ! Compute pressure on intermediate levels: forall(l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps CALL exner_hyb(ps, p3d, pks, pk) - IF (MINVAL(pk) == MAXVAL(pk)) then - print *, '"pk" should not be constant' - stop 1 - end IF + call assert(MINVAL(pk) /= MAXVAL(pk), '"pk" should not be constant') pls = preff * (pk / cpp)**(1. / kappa) PRINT *, "minval(pls) = ", minval(pls) @@ -177,7 +183,7 @@ / apols ENDDO - ! Calcul de l'humidité à saturation : + ! Calcul de l'humidit\'e \`a saturation : qsat = q_sat(t3d, pls) PRINT *, "minval(qsat) = ", minval(qsat) print *, "maxval(qsat) = ", maxval(qsat) @@ -198,16 +204,13 @@ if (nqmx >= 5) then ! Ozone: call regr_lat_time_coefoz - call regr_pr_o3(q(:, :, :, 5)) + call regr_pr_o3(p3d, q(:, :, :, 5)) ! Convert from mole fraction to mass fraction: q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29. end if - tsol = pack(tsol_2d, dyn_phy) - qsol = pack(qsol_2d, dyn_phy) sn = 0. ! snow radsol = 0. - tslab = 0. ! IM "slab" ocean seaice = 0. rugmer = 0.001 zmea = pack(zmea_2d, dyn_phy) @@ -238,12 +241,12 @@ call nf95_close(ncid) - ! Interpolation sur la grille T du modèle : + ! Interpolation sur la grille T du mod\`ele : PRINT *, 'Dimensions de "landiceref.nc"' print *, "iml_lic = ", iml_lic print *, "jml_lic = ", jml_lic - ! Si les coordonnées sont en degrés, on les transforme : + ! Si les coordonn\'ees sont en degr\'es, on les transforme : IF (MAXVAL(dlon_lic) > pi) THEN dlon_lic = dlon_lic * pi / 180. ENDIF @@ -260,7 +263,7 @@ ! Passage sur la grille physique pctsrf = 0. pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy) - ! Adéquation avec le maque terre/mer + ! Ad\'equation avec le maque terre/mer WHERE (pctsrf(:, is_lic) < EPSFRA) pctsrf(:, is_lic) = 0. WHERE (zmasq < EPSFRA) pctsrf(:, is_lic) = 0. pctsrf(:, is_ter) = zmasq @@ -277,18 +280,18 @@ end where end where - ! Sous-surface océan et glace de mer (pour démarrer on met glace - ! de mer à 0) : + ! Sous-surface oc\'ean et glace de mer (pour d\'emarrer on met glace + ! de mer \`a 0) : pctsrf(:, is_oce) = 1. - zmasq WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0. - ! Vérification que somme des sous-surfaces vaut 1 : + ! V\'erification que somme des sous-surfaces vaut 1 : ji = count(abs(sum(pctsrf, dim = 2) - 1.) > EPSFRA) IF (ji /= 0) then - PRINT *, 'Problème répartition sous maille pour ', ji, 'points' + PRINT *, 'Bad surface percentages for ', ji, 'points' end IF - ! Calcul intermédiaire : + ! Calcul interm\'ediaire : CALL massdair(p3d, masse) print *, 'ALPHAX = ', alphax @@ -312,10 +315,6 @@ CALL dynredem1("start.nc", vcov, ucov, teta, q, masse, ps, itau=0) ! Initialisations : - tsolsrf(:, is_ter) = tsol - tsolsrf(:, is_lic) = tsol - tsolsrf(:, is_oce) = tsol - tsolsrf(:, is_sic) = tsol snsrf(:, is_ter) = sn snsrf(:, is_lic) = sn snsrf(:, is_oce) = sn @@ -326,11 +325,8 @@ albe(:, is_sic) = 0.6 alblw = albe evap = 0. - qsolsrf(:, is_ter) = 150. - qsolsrf(:, is_lic) = 150. - qsolsrf(:, is_oce) = 150. - qsolsrf(:, is_sic) = 150. - tsoil = spread(spread(tsol, 2, nsoilmx), 3, nbsrf) + qsolsrf = 150. + tsoil = spread(spread(pack(tsol_2d, dyn_phy), 2, nsoilmx), 3, nbsrf) rain_fall = 0. snow_fall = 0. solsw = 165. @@ -338,8 +334,6 @@ t_ancien = 273.15 q_ancien = 0. agesno = 0. - !IM "slab" ocean - tslab = tsolsrf(:, is_oce) seaice = 0. frugs(:, is_oce) = rugmer @@ -354,11 +348,11 @@ sig1 = 0. w01 = 0. - call phyredem("startphy.nc", latfi, lonfi, pctsrf, & - tsolsrf, tsoil, tslab, seaice, qsolsrf, qsol, snsrf, albe, alblw, & - evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, frugs, & - agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, & - t_ancien, q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01) + call phyredem("startphy.nc", latfi, lonfi, pctsrf, tsoil(:, 1, :), tsoil, & + tsoil(:, 1, is_oce), seaice, qsolsrf, pack(qsol_2d, dyn_phy), snsrf, & + albe, alblw, evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, & + frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, & + q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01) CALL histclo END SUBROUTINE etat0