--- trunk/Sources/dyn3d/etat0.f 2016/03/11 18:47:26 178 +++ trunk/dyn3d/etat0.f 2018/09/06 15:51:09 304 @@ -1,41 +1,30 @@ -module etat0_mod - - use indicesol, only: nbsrf - use dimphy, only: klon +module etat0_m IMPLICIT NONE - REAL pctsrf(klon, nbsrf) - ! ("pctsrf(i, :)" is the composition of the surface at horizontal - ! position "i") - - private nbsrf, klon - contains - SUBROUTINE etat0(phis) + SUBROUTINE etat0(phis, pctsrf) ! From "etat0_netcdf.F", version 1.3, 2005/05/25 13:10:09 use caldyn0_m, only: caldyn0 use comconst, only: cpp, kappa, iniconst use comgeom, only: aire_2d, apoln, apols, cu_2d, cv_2d, inigeom - use conf_gcm_m, only: nday, day_step, iphysiq - use dimens_m, only: iim, jjm, llm, nqmx - use dimphy, only: zmasq + use conf_gcm_m, only: nday + use dimensions, only: iim, jjm, llm, nqmx + use dimphy, only: klon use dimsoil, only: nsoilmx use disvert_m, only: ap, bp, preff, pa, disvert - use dynetat0_m, only: day_ref, annee_ref, xprimp025, xprimm025, rlatu1, & - rlatu2, rlatu, rlatv, yprimu1, yprimu2, rlonu, rlonv, xprimu, xprimv + use dynetat0_m, only: day_ref, annee_ref, rlatu, rlatv, rlonu, rlonv, & + fyhyp, fxhyp use dynredem0_m, only: dynredem0 use dynredem1_m, only: dynredem1 use exner_hyb_m, only: exner_hyb - use fxhyp_m, only: fxhyp - use fyhyp_m, only: fyhyp use geopot_m, only: geopot - use grid_atob, only: grille_m + use grille_m_m, only: grille_m use grid_change, only: init_dyn_phy, dyn_phy - use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra + use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra, nbsrf use iniadvtrac_m, only: iniadvtrac use inifilr_m, only: inifilr use massdair_m, only: massdair @@ -43,14 +32,14 @@ use netcdf95, only: nf95_close, nf95_get_var, nf95_gw_var, nf95_put_var, & nf95_inq_varid, nf95_open use nr_util, only: pi, assert - use phyetat0_m, only: rlat, rlon + use phyetat0_m, only: zmasq, phyetat0_new use phyredem0_m, only: phyredem0, ncid_restartphy use phyredem_m, only: phyredem 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 use startdyn, only: start_init_dyn - USE start_init_orog_m, only: start_init_orog, mask + USE start_init_orog_m, only: start_init_orog use start_init_phys_m, only: start_init_phys use start_inter_3d_m, only: start_inter_3d use test_disvert_m, only: test_disvert @@ -59,6 +48,10 @@ REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1) ! surface geopotential, in m2 s-2 + REAL, intent(out):: pctsrf(:, :) ! (klon, nbsrf) + ! "pctsrf(i, :)" is the composition of the surface at horizontal + ! position "i". + ! Local: REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta @@ -71,7 +64,7 @@ real qsat(iim + 1, jjm + 1, llm) ! mass fraction of saturating water vapor REAL qsolsrf(klon, nbsrf), snsrf(klon, nbsrf) - REAL albe(klon, nbsrf), evap(klon, nbsrf) + REAL albe(klon, nbsrf) REAL tsoil(klon, nsoilmx, nbsrf) REAL null_array(klon) REAL solsw(klon), sollw(klon) @@ -91,7 +84,7 @@ ! D\'eclarations pour lecture glace de mer : INTEGER iml_lic, jml_lic INTEGER ncid, varid - REAL, pointer:: dlon_lic(:), dlat_lic(:) + REAL, ALLOCATABLE:: dlon_lic(:), dlat_lic(:) REAL, ALLOCATABLE:: fraclic(:, :) ! fraction land ice REAL flic_tmp(iim + 1, jjm + 1) ! fraction land ice temporary @@ -130,31 +123,14 @@ pa = 5e4 CALL disvert call test_disvert - - CALL fyhyp(rlatu, rlatv, rlatu2, yprimu2, rlatu1, yprimu1) - CALL fxhyp(xprimm025, rlonv, xprimv, rlonu, xprimu, xprimp025) - - rlatu(1) = pi / 2. - rlatu(jjm + 1) = -rlatu(1) - + CALL fyhyp + CALL fxhyp CALL inigeom CALL inifilr - - rlat(1) = 90. - rlat(2:klon-1) = pack(spread(rlatu(2:jjm), 1, iim), .true.) * 180. / pi - ! (with conversion to degrees) - rlat(klon) = - 90. - - rlon(1) = 0. - rlon(2:klon-1) = pack(spread(rlonv(:iim), 2, jjm - 1), .true.) * 180. / pi - ! (with conversion to degrees) - rlon(klon) = 0. - call start_init_orog(phis, zmea_2d, zstd_2d, zsig_2d, zgam_2d, zthe_2d, & zpic_2d, zval_2d) ! also compute "mask" call init_dyn_phy ! define the mask "dyn_phy" for distinct grid points - zmasq = pack(mask, dyn_phy) - PRINT *, 'Masque construit' + call phyetat0_new call start_init_phys(tsol_2d, qsol_2d) CALL start_init_dyn(tsol_2d, phis, ps) @@ -261,15 +237,14 @@ rlatu) flic_tmp(iim + 1, :) = flic_tmp(1, :) - deallocate(dlon_lic, dlat_lic) ! pointers - - ! Passage sur la grille physique + ! Passage sur la grille physique : pctsrf = 0. pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy) - ! Ad\'equation 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 + where (zmasq <= EPSFRA) pctsrf(:, is_ter) = zmasq where (zmasq > EPSFRA) where (pctsrf(:, is_lic) >= zmasq) pctsrf(:, is_lic) = zmasq @@ -315,7 +290,6 @@ albe(:, is_lic) = 0.6 albe(:, is_oce) = 0.5 albe(:, is_sic) = 0.6 - evap = 0. qsolsrf = 150. tsoil = spread(spread(pack(tsol_2d, dyn_phy), 2, nsoilmx), 3, nbsrf) solsw = 165. @@ -334,18 +308,18 @@ sig1 = 0. w01 = 0. - nday = 0 - call phyredem0(lmt_pas = day_step / iphysiq, itau_phy = 0) + nday = 0 ! side effect + call phyredem0 call nf95_inq_varid(ncid_restartphy, "trs", varid) call nf95_put_var(ncid_restartphy, varid, null_array) call phyredem(pctsrf, tsoil(:, 1, :), tsoil, qsolsrf, & - pack(qsol_2d, dyn_phy), snsrf, albe, evap, null_array, null_array, & - solsw, sollw, null_array, null_array, frugs, agesno, zmea, zstd, & - zsig, zgam, zthe, zpic, zval, t_ancien, q_ancien, rnebcon, ratqs, & - clwcon, null_array, sig1, w01) + pack(qsol_2d, dyn_phy), snsrf, albe, null_array, null_array, solsw, & + sollw, null_array, null_array, frugs, agesno, zmea, zstd, zsig, zgam, & + zthe, zpic, zval, t_ancien, q_ancien, rnebcon, ratqs, clwcon, & + null_array, sig1, w01) END SUBROUTINE etat0 -end module etat0_mod +end module etat0_m