/[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/Sources/dyn3d/etat0.f revision 134 by guez, Wed Apr 29 15:47:56 2015 UTC trunk/dyn3d/etat0.f revision 276 by guez, Thu Jul 12 14:49:20 2018 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(phis)    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 dimens_m, only: iim, jjm, llm, nqmx      use dimensions, only: iim, jjm, llm, nqmx
16      use dimphy, only: zmasq      use dimphy, only: klon
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, pa, disvert
19      use dynetat0_m, only: day_ref, annee_ref      use dynetat0_m, only: day_ref, annee_ref, xprimp025, xprimm025, rlatu1, &
20             rlatu2, rlatu, rlatv, yprimu1, yprimu2, rlonu, rlonv, xprimu, xprimv
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 fxhyp_m, only: fxhyp
25        use fyhyp_m, only: fyhyp
26      use geopot_m, only: geopot      use geopot_m, only: geopot
27      use grid_atob, only: grille_m      use grille_m_m, only: grille_m
28      use grid_change, only: init_dyn_phy, dyn_phy      use grid_change, only: init_dyn_phy, dyn_phy
29      use histclo_m, only: histclo      use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra, nbsrf
     use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra  
30      use iniadvtrac_m, only: iniadvtrac      use iniadvtrac_m, only: iniadvtrac
31      use inifilr_m, only: inifilr      use inifilr_m, only: inifilr
32      use massdair_m, only: massdair      use massdair_m, only: massdair
33      use netcdf, only: nf90_nowrite      use netcdf, only: nf90_nowrite
34      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, &
35           nf95_inq_varid, nf95_open           nf95_inq_varid, nf95_open
36      use nr_util, only: pi, assert      use nr_util, only: pi, assert
37      use paramet_m, only: ip1jm, ip1jmp1      use phyetat0_m, only: rlat, rlon, itau_phy, zmasq
38        use phyredem0_m, only: phyredem0, ncid_restartphy
39      use phyredem_m, only: phyredem      use phyredem_m, only: phyredem
40      use q_sat_m, only: q_sat      use q_sat_m, only: q_sat
41      use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz      use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz
# Line 50  contains Line 44  contains
44      USE start_init_orog_m, only: start_init_orog, mask      USE start_init_orog_m, only: start_init_orog, mask
45      use start_init_phys_m, only: start_init_phys      use start_init_phys_m, only: start_init_phys
46      use start_inter_3d_m, only: start_inter_3d      use start_inter_3d_m, only: start_inter_3d
     use temps, only: itau_phy  
47      use test_disvert_m, only: test_disvert      use test_disvert_m, only: test_disvert
48      use unit_nml_m, only: unit_nml      use unit_nml_m, only: unit_nml
49    
50      REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)      REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)
51      ! surface geopotential, in m2 s-2      ! surface geopotential, in m2 s-2
52    
53      ! Local:      REAL, intent(out):: pctsrf(:, :) ! (klon, nbsrf)
54        ! "pctsrf(i, :)" is the composition of the surface at horizontal
55        ! position "i".
56    
57      REAL latfi(klon), lonfi(klon)      ! Local:
     ! (latitude and longitude of a point of the scalar grid identified  
     ! by a simple index, in degrees)  
58    
59      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta
60      REAL vcov(iim + 1, jjm, llm)      REAL vcov(iim + 1, jjm, llm)
# Line 72  contains Line 65  contains
65      ! and pressure level "pls(i, j, l)".)      ! and pressure level "pls(i, j, l)".)
66    
67      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
     REAL sn(klon)  
68      REAL qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)      REAL qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)
69      REAL albe(klon, nbsrf), evap(klon, nbsrf)      REAL albe(klon, nbsrf), evap(klon, nbsrf)
     REAL alblw(klon, nbsrf)  
70      REAL tsoil(klon, nsoilmx, nbsrf)      REAL tsoil(klon, nsoilmx, nbsrf)
71      REAL radsol(klon), rain_fall(klon), snow_fall(klon)      REAL null_array(klon)
72      REAL solsw(klon), sollw(klon), fder(klon)      REAL solsw(klon), sollw(klon)
73      !IM "slab" ocean      !IM "slab" ocean
     real seaice(klon) ! kg m-2  
74      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)
75      REAL rugmer(klon)      REAL rugmer(klon)
76      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
# Line 91  contains Line 81  contains
81      REAL zthe(klon)      REAL zthe(klon)
82      REAL zpic(klon), zval(klon)      REAL zpic(klon), zval(klon)
83      REAL t_ancien(klon, llm), q_ancien(klon, llm)      REAL t_ancien(klon, llm), q_ancien(klon, llm)
     REAL run_off_lic_0(klon)  
84      real clwcon(klon, llm), rnebcon(klon, llm), ratqs(klon, llm)      real clwcon(klon, llm), rnebcon(klon, llm), ratqs(klon, llm)
85    
86      ! D\'eclarations pour lecture glace de mer :      ! D\'eclarations pour lecture glace de mer :
87      INTEGER iml_lic, jml_lic      INTEGER iml_lic, jml_lic
88      INTEGER ncid, varid      INTEGER ncid, varid
89      REAL, pointer:: dlon_lic(:), dlat_lic(:)      REAL, ALLOCATABLE:: dlon_lic(:), dlat_lic(:)
90      REAL, ALLOCATABLE:: fraclic(:, :) ! fraction land ice      REAL, ALLOCATABLE:: fraclic(:, :) ! fraction land ice
91      REAL flic_tmp(iim + 1, jjm + 1) ! fraction land ice temporary      REAL flic_tmp(iim + 1, jjm + 1) ! fraction land ice temporary
92    
# Line 105  contains Line 94  contains
94    
95      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
96      real pks(iim + 1, jjm + 1)      real pks(iim + 1, jjm + 1)
   
97      REAL masse(iim + 1, jjm + 1, llm)      REAL masse(iim + 1, jjm + 1, llm)
98      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)  
   
99      real sig1(klon, llm) ! section adiabatic updraft      real sig1(klon, llm) ! section adiabatic updraft
100      real w01(klon, llm) ! vertical velocity within adiabatic updraft      real w01(klon, llm) ! vertical velocity within adiabatic updraft
101    
# Line 140  contains Line 125  contains
125      pa = 5e4      pa = 5e4
126      CALL disvert      CALL disvert
127      call test_disvert      call test_disvert
128    
129        CALL fyhyp(rlatu, rlatv, rlatu2, yprimu2, rlatu1, yprimu1)
130        CALL fxhyp(xprimm025, rlonv, xprimv, rlonu, xprimu, xprimp025)
131    
132        rlatu(1) = pi / 2.
133        rlatu(jjm + 1) = -rlatu(1)
134    
135      CALL inigeom      CALL inigeom
136      CALL inifilr      CALL inifilr
137    
138      latfi(1) = 90.      rlat(1) = 90.
139      latfi(2:klon-1) = pack(spread(rlatu(2:jjm), 1, iim), .true.) * 180. / pi      rlat(2:klon-1) = pack(spread(rlatu(2:jjm), 1, iim), .true.) * 180. / pi
140      ! (with conversion to degrees)      ! (with conversion to degrees)
141      latfi(klon) = - 90.      rlat(klon) = - 90.
142    
143      lonfi(1) = 0.      rlon(1) = 0.
144      lonfi(2:klon-1) = pack(spread(rlonv(:iim), 2, jjm - 1), .true.) * 180. / pi      rlon(2:klon-1) = pack(spread(rlonv(:iim), 2, jjm - 1), .true.) * 180. / pi
145      ! (with conversion to degrees)      ! (with conversion to degrees)
146      lonfi(klon) = 0.      rlon(klon) = 0.
147    
148      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, &
149           zpic_2d, zval_2d) ! also compute "mask"           zpic_2d, zval_2d) ! also compute "mask"
# Line 217  contains Line 209  contains
209         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.
210      end if      end if
211    
212      sn = 0. ! snow      null_array = 0.
     radsol = 0.  
     seaice = 0.  
213      rugmer = 0.001      rugmer = 0.001
214      zmea = pack(zmea_2d, dyn_phy)      zmea = pack(zmea_2d, dyn_phy)
215      zstd = pack(zstd_2d, dyn_phy)      zstd = pack(zstd_2d, dyn_phy)
# Line 266  contains Line 256  contains
256           rlatu)           rlatu)
257      flic_tmp(iim + 1, :) = flic_tmp(1, :)      flic_tmp(iim + 1, :) = flic_tmp(1, :)
258    
     deallocate(dlon_lic, dlat_lic) ! pointers  
   
259      ! Passage sur la grille physique      ! Passage sur la grille physique
260      pctsrf = 0.      pctsrf = 0.
261      pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy)      pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy)
262      ! Ad\'equation avec le maque terre/mer      ! Ad\'equation avec le maque terre/mer
263      WHERE (pctsrf(:, is_lic) < EPSFRA) pctsrf(:, is_lic) = 0.      WHERE (pctsrf(:, is_lic) < EPSFRA) pctsrf(:, is_lic) = 0.
264      WHERE (zmasq < EPSFRA) pctsrf(:, is_lic) = 0.      WHERE (zmasq < EPSFRA) pctsrf(:, is_lic) = 0.
265      pctsrf(:, is_ter) = zmasq      where (zmasq <= EPSFRA) pctsrf(:, is_ter) = zmasq
266      where (zmasq > EPSFRA)      where (zmasq > EPSFRA)
267         where (pctsrf(:, is_lic) >= zmasq)         where (pctsrf(:, is_lic) >= zmasq)
268            pctsrf(:, is_lic) = zmasq            pctsrf(:, is_lic) = zmasq
# Line 293  contains Line 281  contains
281      pctsrf(:, is_oce) = 1. - zmasq      pctsrf(:, is_oce) = 1. - zmasq
282      WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0.      WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0.
283    
284      ! V\'erification que somme des sous-surfaces vaut 1 :      ! V\'erification que la somme des sous-surfaces vaut 1 :
285      ji = count(abs(sum(pctsrf, dim = 2) - 1.) > EPSFRA)      ji = count(abs(sum(pctsrf, dim = 2) - 1.) > EPSFRA)
286      IF (ji /= 0) then      IF (ji /= 0) then
287         PRINT *, 'Bad surface percentages for ', ji, 'points'         PRINT *, 'Bad surface percentages for ', ji, 'points'
# Line 308  contains Line 296  contains
296              SUM(aire_2d(:iim, jjm + 1) * masse(:iim, jjm + 1, l)) / apols              SUM(aire_2d(:iim, jjm + 1) * masse(:iim, jjm + 1, l)) / apols
297      END forall      END forall
298    
     ! Initialisation pour traceurs:  
299      call iniadvtrac      call iniadvtrac
     itau_phy = 0  
   
300      CALL geopot(teta, pk , pks, phis, phi)      CALL geopot(teta, pk , pks, phis, phi)
301      CALL caldyn0(ucov, vcov, teta, ps, masse, pk, phis, phi, w, pbaru, &      CALL caldyn0(ucov, vcov, teta, ps, pk, phis, phi)
302           pbarv)      CALL dynredem0(day_ref, phis)
303      CALL dynredem0("start.nc", day_ref, phis)      CALL dynredem1(vcov, ucov, teta, q, masse, ps, itau = 0)
     CALL dynredem1("start.nc", vcov, ucov, teta, q, masse, ps, itau=0)  
304    
305      ! Initialisations :      ! Initialisations :
306      snsrf(:, is_ter) = sn      snsrf = 0.
     snsrf(:, is_lic) = sn  
     snsrf(:, is_oce) = sn  
     snsrf(:, is_sic) = sn  
307      albe(:, is_ter) = 0.08      albe(:, is_ter) = 0.08
308      albe(:, is_lic) = 0.6      albe(:, is_lic) = 0.6
309      albe(:, is_oce) = 0.5      albe(:, is_oce) = 0.5
310      albe(:, is_sic) = 0.6      albe(:, is_sic) = 0.6
     alblw = albe  
311      evap = 0.      evap = 0.
312      qsolsrf = 150.      qsolsrf = 150.
313      tsoil = spread(spread(pack(tsol_2d, dyn_phy), 2, nsoilmx), 3, nbsrf)      tsoil = spread(spread(pack(tsol_2d, dyn_phy), 2, nsoilmx), 3, nbsrf)
     rain_fall = 0.  
     snow_fall = 0.  
314      solsw = 165.      solsw = 165.
315      sollw = -53.      sollw = -53.
316      t_ancien = 273.15      t_ancien = 273.15
317      q_ancien = 0.      q_ancien = 0.
318      agesno = 0.      agesno = 0.
     seaice = 0.  
319    
320      frugs(:, is_oce) = rugmer      frugs(:, is_oce) = rugmer
321      frugs(:, is_ter) = MAX(1e-5, zstd * zsig / 2)      frugs(:, is_ter) = MAX(1e-5, zstd * zsig / 2)
322      frugs(:, is_lic) = MAX(1e-5, zstd * zsig / 2)      frugs(:, is_lic) = MAX(1e-5, zstd * zsig / 2)
323      frugs(:, is_sic) = 0.001      frugs(:, is_sic) = 0.001
     fder = 0.  
324      clwcon = 0.      clwcon = 0.
325      rnebcon = 0.      rnebcon = 0.
326      ratqs = 0.      ratqs = 0.
     run_off_lic_0 = 0.  
327      sig1 = 0.      sig1 = 0.
328      w01 = 0.      w01 = 0.
329    
330      call phyredem("startphy.nc", latfi, lonfi, pctsrf, tsoil(:, 1, :), tsoil, &      nday = 0
331           tsoil(:, 1, is_oce), seaice, qsolsrf, pack(qsol_2d, dyn_phy), snsrf, &      itau_phy = 0 ! side effect
332           albe, alblw, evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, &      call phyredem0
333           frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, &  
334           q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)      call nf95_inq_varid(ncid_restartphy, "trs", varid)
335      CALL histclo      call nf95_put_var(ncid_restartphy, varid, null_array)
336    
337        call phyredem(pctsrf, tsoil(:, 1, :), tsoil, qsolsrf, &
338             pack(qsol_2d, dyn_phy), snsrf, albe, evap, null_array, null_array, &
339             solsw, sollw, null_array, null_array, frugs, agesno, zmea, zstd, &
340             zsig, zgam, zthe, zpic, zval, t_ancien, q_ancien, rnebcon, ratqs, &
341             clwcon, null_array, sig1, w01)
342    
343    END SUBROUTINE etat0    END SUBROUTINE etat0
344    
345  end module etat0_mod  end module etat0_m

Legend:
Removed from v.134  
changed lines
  Added in v.276

  ViewVC Help
Powered by ViewVC 1.1.21