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

Diff of /trunk/dyn3d/etat0.f

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

revision 97 by guez, Fri Apr 25 14:58:31 2014 UTC revision 302 by guez, Thu Sep 6 13:19:51 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    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, pa, disvert
19        use dynetat0_m, only: day_ref, annee_ref, rlatu, rlatv, rlonu, rlonv, &
20             fyhyp, fxhyp
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
     use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra  
28      use iniadvtrac_m, only: iniadvtrac      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: zmasq, 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
45      use temps, only: itau_phy, annee_ref, day_ref      use test_disvert_m, only: test_disvert
46        use unit_nml_m, only: unit_nml
47    
48        REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)
49        ! surface geopotential, in m2 s-2
50    
51      ! Variables local to the procedure:      REAL, intent(out):: pctsrf(:, :) ! (klon, nbsrf)
52        ! "pctsrf(i, :)" is the composition of the surface at horizontal
53        ! position "i".
54    
55      REAL latfi(klon), lonfi(klon)      ! Local:
     ! (latitude and longitude of a point of the scalar grid identified  
     ! by a simple index, in degrees)  
56    
57      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta
58      REAL vcov(iim + 1, jjm, llm)      REAL vcov(iim + 1, jjm, llm)
# Line 68  contains Line 63  contains
63      ! and pressure level "pls(i, j, l)".)      ! and pressure level "pls(i, j, l)".)
64    
65      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
66      REAL tsol(klon), qsol(klon), sn(klon)      REAL qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)
     REAL tsolsrf(klon, nbsrf), qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)  
67      REAL albe(klon, nbsrf), evap(klon, nbsrf)      REAL albe(klon, nbsrf), evap(klon, nbsrf)
     REAL alblw(klon, nbsrf)  
68      REAL tsoil(klon, nsoilmx, nbsrf)      REAL tsoil(klon, nsoilmx, nbsrf)
69      REAL radsol(klon), rain_fall(klon), snow_fall(klon)      REAL null_array(klon)
70      REAL solsw(klon), sollw(klon), fder(klon)      REAL solsw(klon), sollw(klon)
71      !IM "slab" ocean      !IM "slab" ocean
     REAL tslab(klon)  
     real seaice(klon) ! kg m-2  
72      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)
73      REAL rugmer(klon)      REAL rugmer(klon)
     REAL phis(iim + 1, jjm + 1) ! surface geopotential, in m2 s-2  
74      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
75      real, dimension(iim + 1, jjm + 1):: zthe_2d, zpic_2d, zval_2d      real, dimension(iim + 1, jjm + 1):: zthe_2d, zpic_2d, zval_2d
76      real, dimension(iim + 1, jjm + 1):: tsol_2d, qsol_2d, ps      real, dimension(iim + 1, jjm + 1):: tsol_2d, qsol_2d, ps
# Line 89  contains Line 79  contains
79      REAL zthe(klon)      REAL zthe(klon)
80      REAL zpic(klon), zval(klon)      REAL zpic(klon), zval(klon)
81      REAL t_ancien(klon, llm), q_ancien(klon, llm)      REAL t_ancien(klon, llm), q_ancien(klon, llm)
     REAL run_off_lic_0(klon)  
82      real clwcon(klon, llm), rnebcon(klon, llm), ratqs(klon, llm)      real clwcon(klon, llm), rnebcon(klon, llm), ratqs(klon, llm)
83    
84      ! D\'eclarations pour lecture glace de mer :      ! D\'eclarations pour lecture glace de mer :
85      INTEGER iml_lic, jml_lic      INTEGER iml_lic, jml_lic
86      INTEGER ncid, varid      INTEGER ncid, varid
87      REAL, pointer:: dlon_lic(:), dlat_lic(:)      REAL, ALLOCATABLE:: dlon_lic(:), dlat_lic(:)
88      REAL, ALLOCATABLE:: fraclic(:, :) ! fraction land ice      REAL, ALLOCATABLE:: fraclic(:, :) ! fraction land ice
89      REAL flic_tmp(iim + 1, jjm + 1) ! fraction land ice temporary      REAL flic_tmp(iim + 1, jjm + 1) ! fraction land ice temporary
90    
# Line 103  contains Line 92  contains
92    
93      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
94      real pks(iim + 1, jjm + 1)      real pks(iim + 1, jjm + 1)
   
95      REAL masse(iim + 1, jjm + 1, llm)      REAL masse(iim + 1, jjm + 1, llm)
96      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)  
   
97      real sig1(klon, llm) ! section adiabatic updraft      real sig1(klon, llm) ! section adiabatic updraft
98      real w01(klon, llm) ! vertical velocity within adiabatic updraft      real w01(klon, llm) ! vertical velocity within adiabatic updraft
99    
# Line 121  contains Line 106  contains
106      ! ("p3d(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",      ! ("p3d(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",
107      ! for interface "l")      ! for interface "l")
108    
109        namelist /etat0_nml/ day_ref, annee_ref
110    
111      !---------------------------------      !---------------------------------
112    
113      print *, "Call sequence information: etat0"      print *, "Call sequence information: etat0"
114    
115        print *, "Enter namelist 'etat0_nml'."
116        read(unit=*, nml=etat0_nml)
117        write(unit_nml, nml=etat0_nml)
118    
119      CALL iniconst      CALL iniconst
120    
121      ! Construct a grid:      ! Construct a grid:
122    
123      pa = 5e4      pa = 5e4
124      CALL disvert      CALL disvert
125        call test_disvert
126        CALL fyhyp
127        CALL fxhyp
128      CALL inigeom      CALL inigeom
129      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.  
   
130      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, &
131           zpic_2d, zval_2d) ! also compute "mask"           zpic_2d, zval_2d) ! also compute "mask"
132      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
133      zmasq = pack(mask, dyn_phy)      call phyetat0_new
     PRINT *, 'Masque construit'  
134    
135      call start_init_phys(tsol_2d, qsol_2d)      call start_init_phys(tsol_2d, qsol_2d)
136      CALL start_init_dyn(tsol_2d, phis, ps)      CALL start_init_dyn(tsol_2d, phis, ps)
# Line 208  contains Line 190  contains
190         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.
191      end if      end if
192    
193      tsol = pack(tsol_2d, dyn_phy)      null_array = 0.
     qsol = pack(qsol_2d, dyn_phy)  
     sn = 0. ! snow  
     radsol = 0.  
     tslab = 0. ! IM "slab" ocean  
     seaice = 0.  
194      rugmer = 0.001      rugmer = 0.001
195      zmea = pack(zmea_2d, dyn_phy)      zmea = pack(zmea_2d, dyn_phy)
196      zstd = pack(zstd_2d, dyn_phy)      zstd = pack(zstd_2d, dyn_phy)
# Line 260  contains Line 237  contains
237           rlatu)           rlatu)
238      flic_tmp(iim + 1, :) = flic_tmp(1, :)      flic_tmp(iim + 1, :) = flic_tmp(1, :)
239    
240      deallocate(dlon_lic, dlat_lic) ! pointers      ! Passage sur la grille physique :
   
     ! Passage sur la grille physique  
241      pctsrf = 0.      pctsrf = 0.
242      pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy)      pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy)
243      ! Ad\'equation avec le maque terre/mer      
244        ! Ad\'equation avec le maque terre/mer :
245      WHERE (pctsrf(:, is_lic) < EPSFRA) pctsrf(:, is_lic) = 0.      WHERE (pctsrf(:, is_lic) < EPSFRA) pctsrf(:, is_lic) = 0.
246      WHERE (zmasq < EPSFRA) pctsrf(:, is_lic) = 0.      WHERE (zmasq < EPSFRA) pctsrf(:, is_lic) = 0.
247      pctsrf(:, is_ter) = zmasq      where (zmasq <= EPSFRA) pctsrf(:, is_ter) = zmasq
248      where (zmasq > EPSFRA)      where (zmasq > EPSFRA)
249         where (pctsrf(:, is_lic) >= zmasq)         where (pctsrf(:, is_lic) >= zmasq)
250            pctsrf(:, is_lic) = zmasq            pctsrf(:, is_lic) = zmasq
# Line 287  contains Line 263  contains
263      pctsrf(:, is_oce) = 1. - zmasq      pctsrf(:, is_oce) = 1. - zmasq
264      WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0.      WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0.
265    
266      ! V\'erification que somme des sous-surfaces vaut 1 :      ! V\'erification que la somme des sous-surfaces vaut 1 :
267      ji = count(abs(sum(pctsrf, dim = 2) - 1.) > EPSFRA)      ji = count(abs(sum(pctsrf, dim = 2) - 1.) > EPSFRA)
268      IF (ji /= 0) then      IF (ji /= 0) then
269         PRINT *, 'Bad surface percentages for ', ji, 'points'         PRINT *, 'Bad surface percentages for ', ji, 'points'
# Line 296  contains Line 272  contains
272      ! Calcul interm\'ediaire :      ! Calcul interm\'ediaire :
273      CALL massdair(p3d, masse)      CALL massdair(p3d, masse)
274    
     print *, 'ALPHAX = ', alphax  
   
275      forall (l = 1:llm)      forall (l = 1:llm)
276         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
277         masse(:, jjm + 1, l) = &         masse(:, jjm + 1, l) = &
278              SUM(aire_2d(:iim, jjm + 1) * masse(:iim, jjm + 1, l)) / apols              SUM(aire_2d(:iim, jjm + 1) * masse(:iim, jjm + 1, l)) / apols
279      END forall      END forall
280    
     ! Initialisation pour traceurs:  
281      call iniadvtrac      call iniadvtrac
     itau_phy = 0  
     day_ref = dayref  
     annee_ref = anneeref  
   
282      CALL geopot(teta, pk , pks, phis, phi)      CALL geopot(teta, pk , pks, phis, phi)
283      CALL caldyn0(ucov, vcov, teta, ps, masse, pk, phis, phi, w, pbaru, &      CALL caldyn0(ucov, vcov, teta, ps, pk, phis, phi)
284           pbarv)      CALL dynredem0(day_ref, phis)
285      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)  
286    
287      ! Initialisations :      ! Initialisations :
288      tsolsrf(:, is_ter) = tsol      snsrf = 0.
     tsolsrf(:, is_lic) = tsol  
     tsolsrf(:, is_oce) = tsol  
     tsolsrf(:, is_sic) = tsol  
     snsrf(:, is_ter) = sn  
     snsrf(:, is_lic) = sn  
     snsrf(:, is_oce) = sn  
     snsrf(:, is_sic) = sn  
289      albe(:, is_ter) = 0.08      albe(:, is_ter) = 0.08
290      albe(:, is_lic) = 0.6      albe(:, is_lic) = 0.6
291      albe(:, is_oce) = 0.5      albe(:, is_oce) = 0.5
292      albe(:, is_sic) = 0.6      albe(:, is_sic) = 0.6
     alblw = albe  
293      evap = 0.      evap = 0.
294      qsolsrf(:, is_ter) = 150.      qsolsrf = 150.
295      qsolsrf(:, is_lic) = 150.      tsoil = spread(spread(pack(tsol_2d, dyn_phy), 2, nsoilmx), 3, nbsrf)
     qsolsrf(:, is_oce) = 150.  
     qsolsrf(:, is_sic) = 150.  
     tsoil = spread(spread(tsol, 2, nsoilmx), 3, nbsrf)  
     rain_fall = 0.  
     snow_fall = 0.  
296      solsw = 165.      solsw = 165.
297      sollw = -53.      sollw = -53.
298      t_ancien = 273.15      t_ancien = 273.15
299      q_ancien = 0.      q_ancien = 0.
300      agesno = 0.      agesno = 0.
     !IM "slab" ocean  
     tslab = tsolsrf(:, is_oce)  
     seaice = 0.  
301    
302      frugs(:, is_oce) = rugmer      frugs(:, is_oce) = rugmer
303      frugs(:, is_ter) = MAX(1e-5, zstd * zsig / 2)      frugs(:, is_ter) = MAX(1e-5, zstd * zsig / 2)
304      frugs(:, is_lic) = MAX(1e-5, zstd * zsig / 2)      frugs(:, is_lic) = MAX(1e-5, zstd * zsig / 2)
305      frugs(:, is_sic) = 0.001      frugs(:, is_sic) = 0.001
     fder = 0.  
306      clwcon = 0.      clwcon = 0.
307      rnebcon = 0.      rnebcon = 0.
308      ratqs = 0.      ratqs = 0.
     run_off_lic_0 = 0.  
309      sig1 = 0.      sig1 = 0.
310      w01 = 0.      w01 = 0.
311    
312      call phyredem("startphy.nc", latfi, lonfi, pctsrf, &      nday = 0 ! side effect
313           tsolsrf, tsoil, tslab, seaice, qsolsrf, qsol, snsrf, albe, alblw, &      call phyredem0
314           evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, frugs, &  
315           agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &      call nf95_inq_varid(ncid_restartphy, "trs", varid)
316           t_ancien, q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)      call nf95_put_var(ncid_restartphy, varid, null_array)
317      CALL histclo  
318        call phyredem(pctsrf, tsoil(:, 1, :), tsoil, qsolsrf, &
319             pack(qsol_2d, dyn_phy), snsrf, albe, evap, null_array, null_array, &
320             solsw, sollw, null_array, null_array, frugs, agesno, zmea, zstd, &
321             zsig, zgam, zthe, zpic, zval, t_ancien, q_ancien, rnebcon, ratqs, &
322             clwcon, null_array, sig1, w01)
323    
324    END SUBROUTINE etat0    END SUBROUTINE etat0
325    
326  end module etat0_mod  end module etat0_m

Legend:
Removed from v.97  
changed lines
  Added in v.302

  ViewVC Help
Powered by ViewVC 1.1.21