/[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 107 by guez, Thu Sep 11 15:09:15 2014 UTC trunk/Sources/dyn3d/etat0.f revision 175 by guez, Fri Feb 5 16:02:34 2016 UTC
# Line 19  contains Line 19  contains
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
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
     use temps, only: itau_phy, annee_ref, day_ref  
57      use test_disvert_m, only: test_disvert      use test_disvert_m, only: test_disvert
58        use unit_nml_m, only: unit_nml
59    
60      REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)      REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)
61      ! surface geopotential, in m2 s-2      ! surface geopotential, in m2 s-2
62    
63      ! Local:      ! Local:
64    
     REAL latfi(klon), lonfi(klon)  
     ! (latitude and longitude of a point of the scalar grid identified  
     ! by a simple index, in degrees)  
   
65      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta
66      REAL vcov(iim + 1, jjm, llm)      REAL vcov(iim + 1, jjm, llm)
67    
# Line 72  contains Line 71  contains
71      ! and pressure level "pls(i, j, l)".)      ! and pressure level "pls(i, j, l)".)
72    
73      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)  
74      REAL qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)      REAL qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)
75      REAL albe(klon, nbsrf), evap(klon, nbsrf)      REAL albe(klon, nbsrf), evap(klon, nbsrf)
     REAL alblw(klon, nbsrf)  
76      REAL tsoil(klon, nsoilmx, nbsrf)      REAL tsoil(klon, nsoilmx, nbsrf)
77      REAL radsol(klon), rain_fall(klon), snow_fall(klon)      REAL null_array(klon)
78      REAL solsw(klon), sollw(klon), fder(klon)      REAL solsw(klon), sollw(klon)
79      !IM "slab" ocean      !IM "slab" ocean
     real seaice(klon) ! kg m-2  
80      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)
81      REAL rugmer(klon)      REAL rugmer(klon)
82      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 87  contains
87      REAL zthe(klon)      REAL zthe(klon)
88      REAL zpic(klon), zval(klon)      REAL zpic(klon), zval(klon)
89      REAL t_ancien(klon, llm), q_ancien(klon, llm)      REAL t_ancien(klon, llm), q_ancien(klon, llm)
     REAL run_off_lic_0(klon)  
90      real clwcon(klon, llm), rnebcon(klon, llm), ratqs(klon, llm)      real clwcon(klon, llm), rnebcon(klon, llm), ratqs(klon, llm)
91    
92      ! D\'eclarations pour lecture glace de mer :      ! D\'eclarations pour lecture glace de mer :
# Line 105  contains Line 100  contains
100    
101      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
102      real pks(iim + 1, jjm + 1)      real pks(iim + 1, jjm + 1)
   
103      REAL masse(iim + 1, jjm + 1, llm)      REAL masse(iim + 1, jjm + 1, llm)
104      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)  
   
105      real sig1(klon, llm) ! section adiabatic updraft      real sig1(klon, llm) ! section adiabatic updraft
106      real w01(klon, llm) ! vertical velocity within adiabatic updraft      real w01(klon, llm) ! vertical velocity within adiabatic updraft
107    
# Line 123  contains Line 114  contains
114      ! ("p3d(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",      ! ("p3d(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",
115      ! for interface "l")      ! for interface "l")
116    
117        namelist /etat0_nml/ day_ref, annee_ref
118    
119      !---------------------------------      !---------------------------------
120    
121      print *, "Call sequence information: etat0"      print *, "Call sequence information: etat0"
122    
123        print *, "Enter namelist 'etat0_nml'."
124        read(unit=*, nml=etat0_nml)
125        write(unit_nml, nml=etat0_nml)
126    
127      CALL iniconst      CALL iniconst
128    
129      ! Construct a grid:      ! Construct a grid:
# Line 134  contains Line 131  contains
131      pa = 5e4      pa = 5e4
132      CALL disvert      CALL disvert
133      call test_disvert      call test_disvert
134    
135        CALL fyhyp(rlatu, rlatv, rlatu2, yprimu2, rlatu1, yprimu1)
136        CALL fxhyp(xprimm025, rlonv, xprimv, rlonu, xprimu, xprimp025)
137    
138        rlatu(1) = pi / 2.
139        rlatu(jjm + 1) = -rlatu(1)
140    
141      CALL inigeom      CALL inigeom
142      CALL inifilr      CALL inifilr
143    
144      latfi(1) = 90.      rlat(1) = 90.
145      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
146      ! (with conversion to degrees)      ! (with conversion to degrees)
147      latfi(klon) = - 90.      rlat(klon) = - 90.
148    
149      lonfi(1) = 0.      rlon(1) = 0.
150      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
151      ! (with conversion to degrees)      ! (with conversion to degrees)
152      lonfi(klon) = 0.      rlon(klon) = 0.
153    
154      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, &
155           zpic_2d, zval_2d) ! also compute "mask"           zpic_2d, zval_2d) ! also compute "mask"
# Line 211  contains Line 215  contains
215         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.
216      end if      end if
217    
218      sn = 0. ! snow      null_array = 0.
     radsol = 0.  
     seaice = 0.  
219      rugmer = 0.001      rugmer = 0.001
220      zmea = pack(zmea_2d, dyn_phy)      zmea = pack(zmea_2d, dyn_phy)
221      zstd = pack(zstd_2d, dyn_phy)      zstd = pack(zstd_2d, dyn_phy)
# Line 287  contains Line 289  contains
289      pctsrf(:, is_oce) = 1. - zmasq      pctsrf(:, is_oce) = 1. - zmasq
290      WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0.      WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0.
291    
292      ! V\'erification que somme des sous-surfaces vaut 1 :      ! V\'erification que la somme des sous-surfaces vaut 1 :
293      ji = count(abs(sum(pctsrf, dim = 2) - 1.) > EPSFRA)      ji = count(abs(sum(pctsrf, dim = 2) - 1.) > EPSFRA)
294      IF (ji /= 0) then      IF (ji /= 0) then
295         PRINT *, 'Bad surface percentages for ', ji, 'points'         PRINT *, 'Bad surface percentages for ', ji, 'points'
# Line 296  contains Line 298  contains
298      ! Calcul interm\'ediaire :      ! Calcul interm\'ediaire :
299      CALL massdair(p3d, masse)      CALL massdair(p3d, masse)
300    
     print *, 'ALPHAX = ', alphax  
   
301      forall (l = 1:llm)      forall (l = 1:llm)
302         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
303         masse(:, jjm + 1, l) = &         masse(:, jjm + 1, l) = &
304              SUM(aire_2d(:iim, jjm + 1) * masse(:iim, jjm + 1, l)) / apols              SUM(aire_2d(:iim, jjm + 1) * masse(:iim, jjm + 1, l)) / apols
305      END forall      END forall
306    
     ! Initialisation pour traceurs:  
307      call iniadvtrac      call iniadvtrac
     itau_phy = 0  
     day_ref = dayref  
     annee_ref = anneeref  
   
308      CALL geopot(teta, pk , pks, phis, phi)      CALL geopot(teta, pk , pks, phis, phi)
309      CALL caldyn0(ucov, vcov, teta, ps, masse, pk, phis, phi, w, pbaru, &      CALL caldyn0(ucov, vcov, teta, ps, pk, phis, phi)
310           pbarv)      CALL dynredem0(day_ref, phis)
311      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)  
312    
313      ! Initialisations :      ! Initialisations :
314      snsrf(:, is_ter) = sn      snsrf = 0.
     snsrf(:, is_lic) = sn  
     snsrf(:, is_oce) = sn  
     snsrf(:, is_sic) = sn  
315      albe(:, is_ter) = 0.08      albe(:, is_ter) = 0.08
316      albe(:, is_lic) = 0.6      albe(:, is_lic) = 0.6
317      albe(:, is_oce) = 0.5      albe(:, is_oce) = 0.5
318      albe(:, is_sic) = 0.6      albe(:, is_sic) = 0.6
     alblw = albe  
319      evap = 0.      evap = 0.
320      qsolsrf = 150.      qsolsrf = 150.
321      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.  
322      solsw = 165.      solsw = 165.
323      sollw = -53.      sollw = -53.
324      t_ancien = 273.15      t_ancien = 273.15
325      q_ancien = 0.      q_ancien = 0.
326      agesno = 0.      agesno = 0.
     seaice = 0.  
327    
328      frugs(:, is_oce) = rugmer      frugs(:, is_oce) = rugmer
329      frugs(:, is_ter) = MAX(1e-5, zstd * zsig / 2)      frugs(:, is_ter) = MAX(1e-5, zstd * zsig / 2)
330      frugs(:, is_lic) = MAX(1e-5, zstd * zsig / 2)      frugs(:, is_lic) = MAX(1e-5, zstd * zsig / 2)
331      frugs(:, is_sic) = 0.001      frugs(:, is_sic) = 0.001
     fder = 0.  
332      clwcon = 0.      clwcon = 0.
333      rnebcon = 0.      rnebcon = 0.
334      ratqs = 0.      ratqs = 0.
     run_off_lic_0 = 0.  
335      sig1 = 0.      sig1 = 0.
336      w01 = 0.      w01 = 0.
337    
338      call phyredem("startphy.nc", latfi, lonfi, pctsrf, tsoil(:, 1, :), tsoil, &      nday = 0
339           tsoil(:, 1, is_oce), seaice, qsolsrf, pack(qsol_2d, dyn_phy), snsrf, &      call phyredem0(lmt_pas = day_step / iphysiq, itau_phy = 0)
340           albe, alblw, evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, &  
341           frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, &      call nf95_inq_varid(ncid_restartphy, "trs", varid)
342           q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)      call nf95_put_var(ncid_restartphy, varid, null_array)
343      CALL histclo  
344        call phyredem(pctsrf, tsoil(:, 1, :), tsoil, qsolsrf, &
345             pack(qsol_2d, dyn_phy), snsrf, albe, evap, null_array, null_array, &
346             solsw, sollw, null_array, null_array, frugs, agesno, zmea, zstd, &
347             zsig, zgam, zthe, zpic, zval, t_ancien, q_ancien, rnebcon, ratqs, &
348             clwcon, null_array, sig1, w01)
349    
350    END SUBROUTINE etat0    END SUBROUTINE etat0
351    

Legend:
Removed from v.107  
changed lines
  Added in v.175

  ViewVC Help
Powered by ViewVC 1.1.21