/[lmdze]/trunk/dyn3d/etat0.f90
ViewVC logotype

Diff of /trunk/dyn3d/etat0.f90

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

trunk/dyn3d/etat0.f revision 99 by guez, Wed Jul 2 18:39:15 2014 UTC trunk/dyn3d/etat0.f90 revision 344 by guez, Tue Nov 12 15:18:14 2019 UTC
# Line 1  Line 1 
1  module etat0_mod  module etat0_m
   
   use indicesol, only: nbsrf  
   use dimphy, only: klon  
2    
3    IMPLICIT NONE    IMPLICIT NONE
4    
   REAL pctsrf(klon, nbsrf)  
   ! ("pctsrf(i, :)" is the composition of the surface at horizontal  
   ! position "i")  
   
   private nbsrf, klon  
   
5  contains  contains
6    
7    SUBROUTINE etat0    SUBROUTINE etat0(phis, pctsrf)
8    
9      ! 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
10    
11      use caldyn0_m, only: caldyn0      use caldyn0_m, only: caldyn0
12      use comconst, only: cpp, kappa, iniconst      use comconst, only: cpp, kappa, iniconst
13      use comgeom, only: rlatu, rlonv, rlonu, rlatv, aire_2d, apoln, apols, &      use comgeom, only: aire_2d, apoln, apols, cu_2d, cv_2d, inigeom
14           cu_2d, cv_2d, inigeom      use conf_gcm_m, only: nday
15      use conf_gcm_m, only: dayref, anneeref      use dimensions, only: iim, jjm, llm, nqmx
16      use dimens_m, only: iim, jjm, llm, nqmx      use dimphy, only: klon
     use dimphy, only: zmasq  
17      use dimsoil, only: nsoilmx      use dimsoil, only: nsoilmx
18      use disvert_m, only: ap, bp, preff, pa, disvert      use disvert_m, only: ap, bp, preff, disvert
19        use dynetat0_m, only: rlatu, rlatv, rlonu, rlonv, fyhyp, fxhyp
20        use dynetat0_chosen_m, only: day_ref
21      use dynredem0_m, only: dynredem0      use dynredem0_m, only: dynredem0
22      use dynredem1_m, only: dynredem1      use dynredem1_m, only: dynredem1
23      use exner_hyb_m, only: exner_hyb      use exner_hyb_m, only: exner_hyb
24      use geopot_m, only: geopot      use geopot_m, only: geopot
25      use grid_atob, only: grille_m      use grille_m_m, only: grille_m
26      use grid_change, only: init_dyn_phy, dyn_phy      use grid_change, only: init_dyn_phy, dyn_phy
27      use histclo_m, only: histclo      use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra, nbsrf
28      use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra      use infotrac_init_m, only: infotrac_init
     use iniadvtrac_m, only: iniadvtrac  
29      use inifilr_m, only: inifilr      use inifilr_m, only: inifilr
30      use massdair_m, only: massdair      use massdair_m, only: massdair
31      use netcdf, only: nf90_nowrite      use netcdf, only: nf90_nowrite
32      use netcdf95, only: nf95_close, nf95_get_var, nf95_gw_var, &      use netcdf95, only: nf95_close, nf95_get_var, nf95_gw_var, nf95_put_var, &
33           nf95_inq_varid, nf95_open           nf95_inq_varid, nf95_open
34      use nr_util, only: pi, assert      use nr_util, only: pi, assert
35      use paramet_m, only: ip1jm, ip1jmp1      use phyetat0_m, only: masque, phyetat0_new
36        use phyredem0_m, only: phyredem0, ncid_restartphy
37      use phyredem_m, only: phyredem      use phyredem_m, only: phyredem
38      use q_sat_m, only: q_sat      use q_sat_m, only: q_sat
39      use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz      use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz
40      use regr_pr_o3_m, only: regr_pr_o3      use regr_pr_o3_m, only: regr_pr_o3
     use serre, only: alphax  
41      use startdyn, only: start_init_dyn      use startdyn, only: start_init_dyn
42      USE start_init_orog_m, only: start_init_orog, mask      USE start_init_orog_m, only: start_init_orog
43      use start_init_phys_m, only: start_init_phys      use start_init_phys_m, only: start_init_phys
44      use start_inter_3d_m, only: start_inter_3d      use start_inter_3d_m, only: start_inter_3d
     use temps, only: itau_phy, annee_ref, day_ref  
45      use test_disvert_m, only: test_disvert      use test_disvert_m, only: test_disvert
46    
47      ! Variables local to the procedure:      REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)
48        ! surface geopotential, in m2 s-2
49    
50        REAL, intent(out):: pctsrf(:, :) ! (klon, nbsrf)
51        ! "pctsrf(i, :)" is the composition of the surface at horizontal
52        ! position "i".
53    
54      REAL latfi(klon), lonfi(klon)      ! Local:
     ! (latitude and longitude of a point of the scalar grid identified  
     ! by a simple index, in degrees)  
55    
56      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta
57      REAL vcov(iim + 1, jjm, llm)      REAL vcov(iim + 1, jjm, llm)
# Line 69  contains Line 62  contains
62      ! and pressure level "pls(i, j, l)".)      ! and pressure level "pls(i, j, l)".)
63    
64      real qsat(iim + 1, jjm + 1, llm) ! mass fraction of saturating water vapor      real qsat(iim + 1, jjm + 1, llm) ! mass fraction of saturating water vapor
65      REAL sn(klon)      REAL qsolsrf(klon, nbsrf), fsnow(klon, nbsrf)
66      REAL qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)      REAL falbe(klon, nbsrf)
67      REAL albe(klon, nbsrf), evap(klon, nbsrf)      REAL ftsoil(klon, nsoilmx, nbsrf)
68      REAL alblw(klon, nbsrf)      REAL null_array(klon)
69      REAL tsoil(klon, nsoilmx, nbsrf)      REAL solsw(klon), sollw(klon)
     REAL radsol(klon), rain_fall(klon), snow_fall(klon)  
     REAL solsw(klon), sollw(klon), fder(klon)  
70      !IM "slab" ocean      !IM "slab" ocean
     real seaice(klon) ! kg m-2  
71      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)
72      REAL rugmer(klon)      REAL rugmer(klon)
     REAL phis(iim + 1, jjm + 1) ! surface geopotential, in m2 s-2  
73      real, dimension(iim + 1, jjm + 1):: zmea_2d, zstd_2d, zsig_2d, zgam_2d      real, dimension(iim + 1, jjm + 1):: zmea_2d, zstd_2d, zsig_2d, zgam_2d
74      real, dimension(iim + 1, jjm + 1):: zthe_2d, zpic_2d, zval_2d      real, dimension(iim + 1, jjm + 1):: zthe_2d, zpic_2d, zval_2d
75      real, dimension(iim + 1, jjm + 1):: tsol_2d, qsol_2d, ps  
76        real tsol_2d(iim + 1, jjm + 1)
77        ! both soil temperature and surface temperature, in K
78    
79        real, dimension(iim + 1, jjm + 1):: qsol_2d, ps
80      REAL zmea(klon), zstd(klon)      REAL zmea(klon), zstd(klon)
81      REAL zsig(klon), zgam(klon)      REAL zsig(klon), zgam(klon)
82      REAL zthe(klon)      REAL zthe(klon)
83      REAL zpic(klon), zval(klon)      REAL zpic(klon), zval(klon)
84      REAL t_ancien(klon, llm), q_ancien(klon, llm)      REAL t_ancien(klon, llm), q_ancien(klon, llm)
     REAL run_off_lic_0(klon)  
85      real clwcon(klon, llm), rnebcon(klon, llm), ratqs(klon, llm)      real clwcon(klon, llm), rnebcon(klon, llm), ratqs(klon, llm)
86    
87      ! D\'eclarations pour lecture glace de mer :      ! D\'eclarations pour lecture glace de mer :
88      INTEGER iml_lic, jml_lic      INTEGER iml_lic, jml_lic
89      INTEGER ncid, varid      INTEGER ncid, varid
90      REAL, pointer:: dlon_lic(:), dlat_lic(:)      REAL, ALLOCATABLE:: dlon_lic(:), dlat_lic(:)
91      REAL, ALLOCATABLE:: fraclic(:, :) ! fraction land ice      REAL, ALLOCATABLE:: landice(:, :) ! fraction land ice
92      REAL flic_tmp(iim + 1, jjm + 1) ! fraction land ice temporary      REAL flic_tmp(iim + 1, jjm + 1) ! fraction land ice temporary
93    
94      INTEGER l, ji      INTEGER l, ji
95    
96      REAL pk(iim + 1, jjm + 1, llm) ! fonction d'Exner aux milieux des couches      REAL pk(iim + 1, jjm + 1, llm) ! fonction d'Exner aux milieux des couches
97      real pks(iim + 1, jjm + 1)      real pks(iim + 1, jjm + 1)
   
98      REAL masse(iim + 1, jjm + 1, llm)      REAL masse(iim + 1, jjm + 1, llm)
99      REAL phi(iim + 1, jjm + 1, llm)      REAL phi(iim + 1, jjm + 1, llm)
     REAL pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)  
     REAL w(iim + 1, jjm + 1, llm)  
   
100      real sig1(klon, llm) ! section adiabatic updraft      real sig1(klon, llm) ! section adiabatic updraft
101      real w01(klon, llm) ! vertical velocity within adiabatic updraft      real w01(klon, llm) ! vertical velocity within adiabatic updraft
102    
# Line 129  contains Line 117  contains
117    
118      ! Construct a grid:      ! Construct a grid:
119    
     pa = 5e4  
120      CALL disvert      CALL disvert
121      call test_disvert      call test_disvert
122        CALL fyhyp
123        CALL fxhyp
124      CALL inigeom      CALL inigeom
125      CALL inifilr      CALL inifilr
   
     latfi(1) = 90.  
     latfi(2:klon-1) = pack(spread(rlatu(2:jjm), 1, iim), .true.) * 180. / pi  
     ! (with conversion to degrees)  
     latfi(klon) = - 90.  
   
     lonfi(1) = 0.  
     lonfi(2:klon-1) = pack(spread(rlonv(:iim), 2, jjm - 1), .true.) * 180. / pi  
     ! (with conversion to degrees)  
     lonfi(klon) = 0.  
   
126      call start_init_orog(phis, zmea_2d, zstd_2d, zsig_2d, zgam_2d, zthe_2d, &      call start_init_orog(phis, zmea_2d, zstd_2d, zsig_2d, zgam_2d, zthe_2d, &
127           zpic_2d, zval_2d) ! also compute "mask"           zpic_2d, zval_2d) ! also compute "mask"
128      call init_dyn_phy ! define the mask "dyn_phy" for distinct grid points      call init_dyn_phy ! define the mask "dyn_phy" for distinct grid points
129      zmasq = pack(mask, dyn_phy)      call phyetat0_new
     PRINT *, 'Masque construit'  
130    
131      call start_init_phys(tsol_2d, qsol_2d)      call start_init_phys(tsol_2d, qsol_2d)
132      CALL start_init_dyn(tsol_2d, phis, ps)      CALL start_init_dyn(tsol_2d, phis, ps)
# Line 209  contains Line 186  contains
186         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.
187      end if      end if
188    
189      sn = 0. ! snow      null_array = 0.
     radsol = 0.  
     seaice = 0.  
190      rugmer = 0.001      rugmer = 0.001
191      zmea = pack(zmea_2d, dyn_phy)      zmea = pack(zmea_2d, dyn_phy)
192      zstd = pack(zstd_2d, dyn_phy)      zstd = pack(zstd_2d, dyn_phy)
# Line 236  contains Line 211  contains
211      jml_lic = size(dlat_lic)      jml_lic = size(dlat_lic)
212    
213      call nf95_inq_varid(ncid, 'landice', varid)      call nf95_inq_varid(ncid, 'landice', varid)
214      ALLOCATE(fraclic(iml_lic, jml_lic))      ALLOCATE(landice(iml_lic, jml_lic))
215      call nf95_get_var(ncid, varid, fraclic)      call nf95_get_var(ncid, varid, landice)
216    
217      call nf95_close(ncid)      call nf95_close(ncid)
218    
# Line 254  contains Line 229  contains
229         dlat_lic = dlat_lic * pi/ 180.         dlat_lic = dlat_lic * pi/ 180.
230      ENDIF      ENDIF
231    
232      flic_tmp(:iim, :) = grille_m(dlon_lic, dlat_lic, fraclic, rlonv(:iim), &      flic_tmp(:iim, :) = grille_m(dlon_lic, dlat_lic, landice, rlonv(:iim), &
233           rlatu)           rlatu)
234      flic_tmp(iim + 1, :) = flic_tmp(1, :)      flic_tmp(iim + 1, :) = flic_tmp(1, :)
235    
236      deallocate(dlon_lic, dlat_lic) ! pointers      ! Passage sur la grille physique :
   
     ! Passage sur la grille physique  
237      pctsrf = 0.      pctsrf = 0.
238      pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy)      pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy)
239      ! Ad\'equation avec le maque terre/mer      
240        ! Ad\'equation avec le maque terre/mer :
241      WHERE (pctsrf(:, is_lic) < EPSFRA) pctsrf(:, is_lic) = 0.      WHERE (pctsrf(:, is_lic) < EPSFRA) pctsrf(:, is_lic) = 0.
242      WHERE (zmasq < EPSFRA) pctsrf(:, is_lic) = 0.      WHERE (masque < EPSFRA) pctsrf(:, is_lic) = 0.
243      pctsrf(:, is_ter) = zmasq      where (masque <= EPSFRA) pctsrf(:, is_ter) = masque
244      where (zmasq > EPSFRA)      where (masque > EPSFRA)
245         where (pctsrf(:, is_lic) >= zmasq)         where (pctsrf(:, is_lic) >= masque)
246            pctsrf(:, is_lic) = zmasq            pctsrf(:, is_lic) = masque
247            pctsrf(:, is_ter) = 0.            pctsrf(:, is_ter) = 0.
248         elsewhere         elsewhere
249            pctsrf(:, is_ter) = zmasq - pctsrf(:, is_lic)            pctsrf(:, is_ter) = masque - pctsrf(:, is_lic)
250            where (pctsrf(:, is_ter) < EPSFRA)            where (pctsrf(:, is_ter) < EPSFRA)
251               pctsrf(:, is_ter) = 0.               pctsrf(:, is_ter) = 0.
252               pctsrf(:, is_lic) = zmasq               pctsrf(:, is_lic) = masque
253            end where            end where
254         end where         end where
255      end where      end where
256    
257      ! Sous-surface oc\'ean et glace de mer (pour d\'emarrer on met glace      ! Sous-surface oc\'ean et glace de mer (pour d\'emarrer on met glace
258      ! de mer \`a 0) :      ! de mer \`a 0) :
259      pctsrf(:, is_oce) = 1. - zmasq      pctsrf(:, is_oce) = 1. - masque
260      WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0.      WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0.
261    
262      ! V\'erification que somme des sous-surfaces vaut 1 :      ! V\'erification que la somme des sous-surfaces vaut 1 :
263      ji = count(abs(sum(pctsrf, dim = 2) - 1.) > EPSFRA)      ji = count(abs(sum(pctsrf, dim = 2) - 1.) > EPSFRA)
264      IF (ji /= 0) then      IF (ji /= 0) then
265         PRINT *, 'Bad surface percentages for ', ji, 'points'         PRINT *, 'Bad surface percentages for ', ji, 'points'
# Line 294  contains Line 268  contains
268      ! Calcul interm\'ediaire :      ! Calcul interm\'ediaire :
269      CALL massdair(p3d, masse)      CALL massdair(p3d, masse)
270    
     print *, 'ALPHAX = ', alphax  
   
271      forall (l = 1:llm)      forall (l = 1:llm)
272         masse(:, 1, l) = SUM(aire_2d(:iim, 1) * masse(:iim, 1, l)) / apoln         masse(:, 1, l) = SUM(aire_2d(:iim, 1) * masse(:iim, 1, l)) / apoln
273         masse(:, jjm + 1, l) = &         masse(:, jjm + 1, l) = &
274              SUM(aire_2d(:iim, jjm + 1) * masse(:iim, jjm + 1, l)) / apols              SUM(aire_2d(:iim, jjm + 1) * masse(:iim, jjm + 1, l)) / apols
275      END forall      END forall
276    
277      ! Initialisation pour traceurs:      call infotrac_init
     call iniadvtrac  
     itau_phy = 0  
     day_ref = dayref  
     annee_ref = anneeref  
   
278      CALL geopot(teta, pk , pks, phis, phi)      CALL geopot(teta, pk , pks, phis, phi)
279      CALL caldyn0(ucov, vcov, teta, ps, masse, pk, phis, phi, w, pbaru, &      CALL caldyn0(ucov, vcov, teta, ps, pk, phis, phi)
280           pbarv)      CALL dynredem0(day_ref, phis)
281      CALL dynredem0("start.nc", dayref, phis)      CALL dynredem1(vcov, ucov, teta, q, masse, ps, itau = 0)
     CALL dynredem1("start.nc", vcov, ucov, teta, q, masse, ps, itau=0)  
282    
283      ! Initialisations :      ! Initialisations :
284      snsrf(:, is_ter) = sn      fsnow = 0.
285      snsrf(:, is_lic) = sn      falbe(:, is_ter) = 0.08
286      snsrf(:, is_oce) = sn      falbe(:, is_lic) = 0.6
287      snsrf(:, is_sic) = sn      falbe(:, is_oce) = 0.5
288      albe(:, is_ter) = 0.08      falbe(:, is_sic) = 0.6
     albe(:, is_lic) = 0.6  
     albe(:, is_oce) = 0.5  
     albe(:, is_sic) = 0.6  
     alblw = albe  
     evap = 0.  
289      qsolsrf = 150.      qsolsrf = 150.
290      tsoil = spread(spread(pack(tsol_2d, dyn_phy), 2, nsoilmx), 3, nbsrf)      ftsoil = spread(spread(pack(tsol_2d, dyn_phy), 2, nsoilmx), 3, nbsrf)
     rain_fall = 0.  
     snow_fall = 0.  
291      solsw = 165.      solsw = 165.
292      sollw = -53.      sollw = -53.
293      t_ancien = 273.15      t_ancien = 273.15
294      q_ancien = 0.      q_ancien = 0.
295      agesno = 0.      agesno = 0.
     seaice = 0.  
296    
297      frugs(:, is_oce) = rugmer      frugs(:, is_oce) = rugmer
298      frugs(:, is_ter) = MAX(1e-5, zstd * zsig / 2)      frugs(:, is_ter) = MAX(1e-5, zstd * zsig / 2)
299      frugs(:, is_lic) = MAX(1e-5, zstd * zsig / 2)      frugs(:, is_lic) = MAX(1e-5, zstd * zsig / 2)
300      frugs(:, is_sic) = 0.001      frugs(:, is_sic) = 0.001
     fder = 0.  
301      clwcon = 0.      clwcon = 0.
302      rnebcon = 0.      rnebcon = 0.
303      ratqs = 0.      ratqs = 0.
     run_off_lic_0 = 0.  
304      sig1 = 0.      sig1 = 0.
305      w01 = 0.      w01 = 0.
306    
307      call phyredem("startphy.nc", latfi, lonfi, pctsrf, tsoil(:, 1, :), tsoil, &      nday = 0 ! side effect
308           tsoil(:, 1, is_oce), seaice, qsolsrf, pack(qsol_2d, dyn_phy), snsrf, &      call phyredem0
309           albe, alblw, evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, &  
310           frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, &      call nf95_inq_varid(ncid_restartphy, "trs", varid)
311           q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)      call nf95_put_var(ncid_restartphy, varid, null_array)
312      CALL histclo  
313        call phyredem(pctsrf, ftsoil(:, 1, :), ftsoil, qsolsrf, &
314             pack(qsol_2d, dyn_phy), fsnow, falbe, null_array, null_array, solsw, &
315             sollw, null_array, null_array, frugs, agesno, zmea, zstd, zsig, zgam, &
316             zthe, zpic, zval, t_ancien, q_ancien, rnebcon, ratqs, clwcon, &
317             null_array, sig1, w01)
318    
319    END SUBROUTINE etat0    END SUBROUTINE etat0
320    
321  end module etat0_mod  end module etat0_m

Legend:
Removed from v.99  
changed lines
  Added in v.344

  ViewVC Help
Powered by ViewVC 1.1.21