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

Diff of /trunk/Sources/dyn3d/etat0.f

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

trunk/dyn3d/etat0.f revision 90 by guez, Wed Mar 12 21:16:36 2014 UTC trunk/Sources/dyn3d/etat0.f revision 163 by guez, Fri Jul 24 18:14:04 2015 UTC
# Line 13  module etat0_mod Line 13  module etat0_mod
13    
14  contains  contains
15    
16    SUBROUTINE etat0    SUBROUTINE etat0(phis)
17    
18      ! 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
19    
20      use caldyn0_m, only: caldyn0      use caldyn0_m, only: caldyn0
21      use comconst, only: cpp, kappa, iniconst      use comconst, only: cpp, kappa, iniconst
22      use comgeom, only: rlatu, rlonv, rlonu, rlatv, aire_2d, apoln, apols, &      use comgeom, only: aire_2d, apoln, apols, cu_2d, cv_2d, inigeom
23           cu_2d, cv_2d, inigeom      use conf_gcm_m, only: nday, day_step, iphysiq
     use conf_gcm_m, only: dayref, anneeref  
24      use dimens_m, only: iim, jjm, llm, nqmx      use dimens_m, only: iim, jjm, llm, nqmx
25      use dimphy, only: zmasq      use dimphy, only: zmasq
26      use dimsoil, only: nsoilmx      use dimsoil, only: nsoilmx
27      use disvert_m, only: ap, bp, preff, pa, disvert      use disvert_m, only: ap, bp, preff, pa, disvert
28        use dynetat0_m, only: day_ref, annee_ref, xprimp025, xprimm025, rlatu1, &
29             rlatu2, rlatu, rlatv, yprimu1, yprimu2, rlonu, rlonv, xprimu, xprimv
30      use dynredem0_m, only: dynredem0      use dynredem0_m, only: dynredem0
31      use dynredem1_m, only: dynredem1      use dynredem1_m, only: dynredem1
32      use exner_hyb_m, only: exner_hyb      use exner_hyb_m, only: exner_hyb
33        use fxhyp_m, only: fxhyp
34        use fyhyp_m, only: fyhyp
35      use geopot_m, only: geopot      use geopot_m, only: geopot
36      use grid_atob, only: grille_m      use grid_atob, only: grille_m
37      use grid_change, only: init_dyn_phy, dyn_phy      use grid_change, only: init_dyn_phy, dyn_phy
     use histclo_m, only: histclo  
38      use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra      use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra
39      use iniadvtrac_m, only: iniadvtrac      use iniadvtrac_m, only: iniadvtrac
40      use inifilr_m, only: inifilr      use inifilr_m, only: inifilr
41      use massdair_m, only: massdair      use massdair_m, only: massdair
42      use netcdf, only: nf90_nowrite      use netcdf, only: nf90_nowrite
43      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, &
44           nf95_inq_varid, nf95_open           nf95_inq_varid, nf95_open
45      use nr_util, only: pi, assert      use nr_util, only: pi, assert
46      use paramet_m, only: ip1jm, ip1jmp1      use paramet_m, only: ip1jm, ip1jmp1
47        use phyetat0_m, only: rlat, rlon
48        use phyredem0_m, only: phyredem0, ncid_restartphy
49      use phyredem_m, only: phyredem      use phyredem_m, only: phyredem
     use pressure_var, only: pls, p3d  
50      use q_sat_m, only: q_sat      use q_sat_m, only: q_sat
51      use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz      use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz
52      use regr_pr_o3_m, only: regr_pr_o3      use regr_pr_o3_m, only: regr_pr_o3
     use serre, only: alphax  
53      use startdyn, only: start_init_dyn      use startdyn, only: start_init_dyn
54      USE start_init_orog_m, only: start_init_orog, mask      USE start_init_orog_m, only: start_init_orog, mask
55      use start_init_phys_m, only: start_init_phys      use start_init_phys_m, only: start_init_phys
56      use start_inter_3d_m, only: start_inter_3d      use start_inter_3d_m, only: start_inter_3d
57      use temps, only: itau_phy, annee_ref, day_ref      use temps, only: itau_phy
58        use test_disvert_m, only: test_disvert
59        use unit_nml_m, only: unit_nml
60    
61      ! Variables local to the procedure:      REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)
62        ! surface geopotential, in m2 s-2
63    
64      REAL latfi(klon), lonfi(klon)      ! Local:
     ! (latitude and longitude of a point of the scalar grid identified  
     ! by a simple index, in degrees)  
65    
66      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta
67      REAL vcov(iim + 1, jjm, llm)      REAL vcov(iim + 1, jjm, llm)
# Line 69  contains Line 72  contains
72      ! and pressure level "pls(i, j, l)".)      ! and pressure level "pls(i, j, l)".)
73    
74      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
75      REAL tsol(klon), qsol(klon), sn(klon)      REAL qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)
     REAL tsolsrf(klon, nbsrf), qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)  
76      REAL albe(klon, nbsrf), evap(klon, nbsrf)      REAL albe(klon, nbsrf), evap(klon, nbsrf)
     REAL alblw(klon, nbsrf)  
77      REAL tsoil(klon, nsoilmx, nbsrf)      REAL tsoil(klon, nsoilmx, nbsrf)
78      REAL radsol(klon), rain_fall(klon), snow_fall(klon)      REAL null_array(klon)
79      REAL solsw(klon), sollw(klon), fder(klon)      REAL solsw(klon), sollw(klon)
80      !IM "slab" ocean      !IM "slab" ocean
     REAL tslab(klon)  
     real seaice(klon) ! kg m-2  
81      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)
82      REAL rugmer(klon)      REAL rugmer(klon)
     REAL phis(iim + 1, jjm + 1) ! surface geopotential, in m2 s-2  
83      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
84      real, dimension(iim + 1, jjm + 1):: zthe_2d, zpic_2d, zval_2d      real, dimension(iim + 1, jjm + 1):: zthe_2d, zpic_2d, zval_2d
85      real, dimension(iim + 1, jjm + 1):: tsol_2d, qsol_2d, ps      real, dimension(iim + 1, jjm + 1):: tsol_2d, qsol_2d, ps
# Line 90  contains Line 88  contains
88      REAL zthe(klon)      REAL zthe(klon)
89      REAL zpic(klon), zval(klon)      REAL zpic(klon), zval(klon)
90      REAL t_ancien(klon, llm), q_ancien(klon, llm)      REAL t_ancien(klon, llm), q_ancien(klon, llm)
     REAL run_off_lic_0(klon)  
91      real clwcon(klon, llm), rnebcon(klon, llm), ratqs(klon, llm)      real clwcon(klon, llm), rnebcon(klon, llm), ratqs(klon, llm)
92    
93      ! D\'eclarations pour lecture glace de mer :      ! D\'eclarations pour lecture glace de mer :
# Line 104  contains Line 101  contains
101    
102      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
103      real pks(iim + 1, jjm + 1)      real pks(iim + 1, jjm + 1)
   
104      REAL masse(iim + 1, jjm + 1, llm)      REAL masse(iim + 1, jjm + 1, llm)
105      REAL phi(iim + 1, jjm + 1, llm)      REAL phi(iim + 1, jjm + 1, llm)
     REAL pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)  
     REAL w(ip1jmp1, llm)  
   
106      real sig1(klon, llm) ! section adiabatic updraft      real sig1(klon, llm) ! section adiabatic updraft
107      real w01(klon, llm) ! vertical velocity within adiabatic updraft      real w01(klon, llm) ! vertical velocity within adiabatic updraft
108    
109        real pls(iim + 1, jjm + 1, llm)
110        ! (pressure at mid-layer of LMDZ grid, in Pa)
111        ! "pls(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",
112        ! for layer "l")
113    
114        REAL p3d(iim + 1, jjm + 1, llm+1) ! pressure at layer interfaces, in Pa
115        ! ("p3d(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",
116        ! for interface "l")
117    
118        namelist /etat0_nml/ day_ref, annee_ref
119    
120      !---------------------------------      !---------------------------------
121    
122      print *, "Call sequence information: etat0"      print *, "Call sequence information: etat0"
123    
124        print *, "Enter namelist 'etat0_nml'."
125        read(unit=*, nml=etat0_nml)
126        write(unit_nml, nml=etat0_nml)
127    
128      CALL iniconst      CALL iniconst
129    
130      ! Construct a grid:      ! Construct a grid:
131    
132      pa = 5e4      pa = 5e4
133      CALL disvert      CALL disvert
134        call test_disvert
135    
136        CALL fyhyp(rlatu, rlatv, rlatu2, yprimu2, rlatu1, yprimu1)
137        CALL fxhyp(xprimm025, rlonv, xprimv, rlonu, xprimu, xprimp025)
138    
139        rlatu(1) = pi / 2.
140        rlatu(jjm + 1) = -rlatu(1)
141    
142      CALL inigeom      CALL inigeom
143      CALL inifilr      CALL inifilr
144    
145      latfi(1) = 90.      rlat(1) = 90.
146      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
147      ! (with conversion to degrees)      ! (with conversion to degrees)
148      latfi(klon) = - 90.      rlat(klon) = - 90.
149    
150      lonfi(1) = 0.      rlon(1) = 0.
151      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
152      ! (with conversion to degrees)      ! (with conversion to degrees)
153      lonfi(klon) = 0.      rlon(klon) = 0.
154    
155      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, &
156           zpic_2d, zval_2d) ! also compute "mask"           zpic_2d, zval_2d) ! also compute "mask"
# Line 195  contains Line 211  contains
211      if (nqmx >= 5) then      if (nqmx >= 5) then
212         ! Ozone:         ! Ozone:
213         call regr_lat_time_coefoz         call regr_lat_time_coefoz
214         call regr_pr_o3(q(:, :, :, 5))         call regr_pr_o3(p3d, q(:, :, :, 5))
215         ! Convert from mole fraction to mass fraction:         ! Convert from mole fraction to mass fraction:
216         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.
217      end if      end if
218    
219      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.  
220      rugmer = 0.001      rugmer = 0.001
221      zmea = pack(zmea_2d, dyn_phy)      zmea = pack(zmea_2d, dyn_phy)
222      zstd = pack(zstd_2d, dyn_phy)      zstd = pack(zstd_2d, dyn_phy)
# Line 279  contains Line 290  contains
290      pctsrf(:, is_oce) = 1. - zmasq      pctsrf(:, is_oce) = 1. - zmasq
291      WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0.      WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0.
292    
293      ! V\'erification que somme des sous-surfaces vaut 1 :      ! V\'erification que la somme des sous-surfaces vaut 1 :
294      ji = count(abs(sum(pctsrf, dim = 2) - 1.) > EPSFRA)      ji = count(abs(sum(pctsrf, dim = 2) - 1.) > EPSFRA)
295      IF (ji /= 0) then      IF (ji /= 0) then
296         PRINT *, 'Probl\`eme r\'epartition sous maille pour ', ji, 'points'         PRINT *, 'Bad surface percentages for ', ji, 'points'
297      end IF      end IF
298    
299      ! Calcul interm\'ediaire :      ! Calcul interm\'ediaire :
300      CALL massdair(p3d, masse)      CALL massdair(p3d, masse)
301    
     print *, 'ALPHAX = ', alphax  
   
302      forall (l = 1:llm)      forall (l = 1:llm)
303         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
304         masse(:, jjm + 1, l) = &         masse(:, jjm + 1, l) = &
305              SUM(aire_2d(:iim, jjm + 1) * masse(:iim, jjm + 1, l)) / apols              SUM(aire_2d(:iim, jjm + 1) * masse(:iim, jjm + 1, l)) / apols
306      END forall      END forall
307    
     ! Initialisation pour traceurs:  
308      call iniadvtrac      call iniadvtrac
     itau_phy = 0  
     day_ref = dayref  
     annee_ref = anneeref  
   
309      CALL geopot(teta, pk , pks, phis, phi)      CALL geopot(teta, pk , pks, phis, phi)
310      CALL caldyn0(ucov, vcov, teta, ps, masse, pk, phis, phi, w, pbaru, &      CALL caldyn0(ucov, vcov, teta, ps, pk, phis, phi)
311           pbarv)      CALL dynredem0(day_ref, phis)
312      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)  
313    
314      ! Initialisations :      ! Initialisations :
315      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  
316      albe(:, is_ter) = 0.08      albe(:, is_ter) = 0.08
317      albe(:, is_lic) = 0.6      albe(:, is_lic) = 0.6
318      albe(:, is_oce) = 0.5      albe(:, is_oce) = 0.5
319      albe(:, is_sic) = 0.6      albe(:, is_sic) = 0.6
     alblw = albe  
320      evap = 0.      evap = 0.
321      qsolsrf(:, is_ter) = 150.      qsolsrf = 150.
322      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.  
323      solsw = 165.      solsw = 165.
324      sollw = -53.      sollw = -53.
325      t_ancien = 273.15      t_ancien = 273.15
326      q_ancien = 0.      q_ancien = 0.
327      agesno = 0.      agesno = 0.
     !IM "slab" ocean  
     tslab = tsolsrf(:, is_oce)  
     seaice = 0.  
328    
329      frugs(:, is_oce) = rugmer      frugs(:, is_oce) = rugmer
330      frugs(:, is_ter) = MAX(1e-5, zstd * zsig / 2)      frugs(:, is_ter) = MAX(1e-5, zstd * zsig / 2)
331      frugs(:, is_lic) = MAX(1e-5, zstd * zsig / 2)      frugs(:, is_lic) = MAX(1e-5, zstd * zsig / 2)
332      frugs(:, is_sic) = 0.001      frugs(:, is_sic) = 0.001
     fder = 0.  
333      clwcon = 0.      clwcon = 0.
334      rnebcon = 0.      rnebcon = 0.
335      ratqs = 0.      ratqs = 0.
     run_off_lic_0 = 0.  
336      sig1 = 0.      sig1 = 0.
337      w01 = 0.      w01 = 0.
338    
339      call phyredem("startphy.nc", latfi, lonfi, pctsrf, &      itau_phy = 0
340           tsolsrf, tsoil, tslab, seaice, qsolsrf, qsol, snsrf, albe, alblw, &      nday = 0
341           evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, frugs, &      call phyredem0(lmt_pas = day_step / iphysiq)
342           agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &  
343           t_ancien, q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)      call nf95_inq_varid(ncid_restartphy, "trs", varid)
344      CALL histclo      call nf95_put_var(ncid_restartphy, varid, null_array)
345    
346        call phyredem(pctsrf, tsoil(:, 1, :), tsoil, tsoil(:, 1, is_oce), &
347             null_array, qsolsrf, pack(qsol_2d, dyn_phy), snsrf, albe, evap, &
348             null_array, null_array, solsw, sollw, null_array, null_array, frugs, &
349             agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, &
350             q_ancien, rnebcon, ratqs, clwcon, null_array, sig1, w01)
351    
352    END SUBROUTINE etat0    END SUBROUTINE etat0
353    

Legend:
Removed from v.90  
changed lines
  Added in v.163

  ViewVC Help
Powered by ViewVC 1.1.21