/[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

revision 134 by guez, Wed Apr 29 15:47:56 2015 UTC revision 157 by guez, Mon Jul 20 16:01:49 2015 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
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      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
# Line 59  contains Line 63  contains
63    
64      ! Local:      ! Local:
65    
     REAL latfi(klon), lonfi(klon)  
     ! (latitude and longitude of a point of the scalar grid identified  
     ! by a simple index, in degrees)  
   
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)
68    
# Line 72  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
     REAL sn(klon)  
75      REAL qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)      REAL 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 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)
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
# Line 91  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 140  contains Line 136  contains
136      pa = 5e4      pa = 5e4
137      CALL disvert      CALL disvert
138      call test_disvert      call test_disvert
139    
140        CALL fyhyp(rlatu, rlatv, rlatu2, yprimu2, rlatu1, yprimu1)
141        CALL fxhyp(xprimm025, rlonv, xprimv, rlonu, xprimu, xprimp025)
142    
143        rlatu(1) = pi / 2.
144        rlatu(jjm + 1) = -rlatu(1)
145    
146      CALL inigeom      CALL inigeom
147      CALL inifilr      CALL inifilr
148    
149      latfi(1) = 90.      rlat(1) = 90.
150      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
151      ! (with conversion to degrees)      ! (with conversion to degrees)
152      latfi(klon) = - 90.      rlat(klon) = - 90.
153    
154      lonfi(1) = 0.      rlon(1) = 0.
155      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
156      ! (with conversion to degrees)      ! (with conversion to degrees)
157      lonfi(klon) = 0.      rlon(klon) = 0.
158    
159      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, &
160           zpic_2d, zval_2d) ! also compute "mask"           zpic_2d, zval_2d) ! also compute "mask"
# Line 217  contains Line 220  contains
220         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.
221      end if      end if
222    
223      sn = 0. ! snow      null_array = 0.
     radsol = 0.  
     seaice = 0.  
224      rugmer = 0.001      rugmer = 0.001
225      zmea = pack(zmea_2d, dyn_phy)      zmea = pack(zmea_2d, dyn_phy)
226      zstd = pack(zstd_2d, dyn_phy)      zstd = pack(zstd_2d, dyn_phy)
# Line 308  contains Line 309  contains
309              SUM(aire_2d(:iim, jjm + 1) * masse(:iim, jjm + 1, l)) / apols              SUM(aire_2d(:iim, jjm + 1) * masse(:iim, jjm + 1, l)) / apols
310      END forall      END forall
311    
     ! Initialisation pour traceurs:  
312      call iniadvtrac      call iniadvtrac
     itau_phy = 0  
   
313      CALL geopot(teta, pk , pks, phis, phi)      CALL geopot(teta, pk , pks, phis, phi)
314      CALL caldyn0(ucov, vcov, teta, ps, masse, pk, phis, phi, w, pbaru, &      CALL caldyn0(ucov, vcov, teta, ps, masse, pk, phis, phi, w, pbaru, pbarv)
315           pbarv)      CALL dynredem0(day_ref, phis)
316      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)  
317    
318      ! Initialisations :      ! Initialisations :
319      snsrf(:, is_ter) = sn      snsrf = 0.
     snsrf(:, is_lic) = sn  
     snsrf(:, is_oce) = sn  
     snsrf(:, is_sic) = sn  
320      albe(:, is_ter) = 0.08      albe(:, is_ter) = 0.08
321      albe(:, is_lic) = 0.6      albe(:, is_lic) = 0.6
322      albe(:, is_oce) = 0.5      albe(:, is_oce) = 0.5
323      albe(:, is_sic) = 0.6      albe(:, is_sic) = 0.6
     alblw = albe  
324      evap = 0.      evap = 0.
325      qsolsrf = 150.      qsolsrf = 150.
326      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.  
327      solsw = 165.      solsw = 165.
328      sollw = -53.      sollw = -53.
329      t_ancien = 273.15      t_ancien = 273.15
330      q_ancien = 0.      q_ancien = 0.
331      agesno = 0.      agesno = 0.
     seaice = 0.  
332    
333      frugs(:, is_oce) = rugmer      frugs(:, is_oce) = rugmer
334      frugs(:, is_ter) = MAX(1e-5, zstd * zsig / 2)      frugs(:, is_ter) = MAX(1e-5, zstd * zsig / 2)
335      frugs(:, is_lic) = MAX(1e-5, zstd * zsig / 2)      frugs(:, is_lic) = MAX(1e-5, zstd * zsig / 2)
336      frugs(:, is_sic) = 0.001      frugs(:, is_sic) = 0.001
     fder = 0.  
337      clwcon = 0.      clwcon = 0.
338      rnebcon = 0.      rnebcon = 0.
339      ratqs = 0.      ratqs = 0.
     run_off_lic_0 = 0.  
340      sig1 = 0.      sig1 = 0.
341      w01 = 0.      w01 = 0.
342    
343      call phyredem("startphy.nc", latfi, lonfi, pctsrf, tsoil(:, 1, :), tsoil, &      itau_phy = 0
344           tsoil(:, 1, is_oce), seaice, qsolsrf, pack(qsol_2d, dyn_phy), snsrf, &      nday = 0
345           albe, alblw, evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, &      call phyredem0(lmt_pas = day_step / iphysiq)
346           frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, &  
347           q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)      call nf95_inq_varid(ncid_restartphy, "trs", varid)
348      CALL histclo      call nf95_put_var(ncid_restartphy, varid, null_array)
349    
350        call phyredem(pctsrf, tsoil(:, 1, :), tsoil, tsoil(:, 1, is_oce), &
351             null_array, qsolsrf, pack(qsol_2d, dyn_phy), snsrf, albe, evap, &
352             null_array, null_array, solsw, sollw, null_array, null_array, frugs, &
353             agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, &
354             q_ancien, rnebcon, ratqs, clwcon, null_array, sig1, w01)
355    
356    END SUBROUTINE etat0    END SUBROUTINE etat0
357    

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

  ViewVC Help
Powered by ViewVC 1.1.21