/[lmdze]/trunk/libf/dyn3d/etat0.f90
ViewVC logotype

Diff of /trunk/libf/dyn3d/etat0.f90

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

revision 18 by guez, Thu Aug 7 12:29:13 2008 UTC revision 32 by guez, Tue Apr 6 17:52:58 2010 UTC
# Line 19  contains Line 19  contains
19    
20      ! This subroutine creates "mask".      ! This subroutine creates "mask".
21    
22      USE ioipsl, only: flinget, flinclo, flinopen_nozoom, flininfo, histclo      use caldyn0_m, only: caldyn0
   
     USE start_init_orog_m, only: start_init_orog, mask, phis  
     use start_init_phys_m, only: qsol_2d  
     use startdyn, only: start_inter_3d, start_init_dyn  
     use dimens_m, only: iim, jjm, llm, nqmx  
     use paramet_m, only: ip1jm, ip1jmp1  
23      use comconst, only: dtvr, daysec, cpp, kappa, pi      use comconst, only: dtvr, daysec, cpp, kappa, pi
     use comdissnew, only: lstardis, nitergdiv, nitergrot, niterh, &  
          tetagdiv, tetagrot, tetatemp  
     use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra  
     use comvert, only: ap, bp, preff, pa  
     use dimphy, only: zmasq  
     use conf_gcm_m, only: day_step, iphysiq, dayref, anneeref  
24      use comgeom, only: rlatu, rlonv, rlonu, rlatv, aire_2d, apoln, apols, &      use comgeom, only: rlatu, rlonv, rlonu, rlatv, aire_2d, apoln, apols, &
25           cu_2d, cv_2d           cu_2d, cv_2d
26      use serre, only: alphax      use comvert, only: ap, bp, preff, pa
27        use conf_gcm_m, only: day_step, iphysiq, dayref, anneeref
28        use dimens_m, only: iim, jjm, llm, nqmx
29        use dimphy, only: zmasq
30      use dimsoil, only: nsoilmx      use dimsoil, only: nsoilmx
31      use temps, only: itau_dyn, itau_phy, annee_ref, day_ref, dt      use dynredem0_m, only: dynredem0
32        use dynredem1_m, only: dynredem1
33        use exner_hyb_m, only: exner_hyb
34      use grid_atob, only: grille_m      use grid_atob, only: grille_m
35      use grid_change, only: init_dyn_phy, dyn_phy      use grid_change, only: init_dyn_phy, dyn_phy
36      use q_sat_m, only: q_sat      use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra
     use exner_hyb_m, only: exner_hyb  
37      use iniadvtrac_m, only: iniadvtrac      use iniadvtrac_m, only: iniadvtrac
38        use inidissip_m, only: inidissip
39        use inigeom_m, only: inigeom
40        USE flincom, only: flinclo, flinopen_nozoom, flininfo
41        use flinget_m, only: flinget
42        use histcom, only: histclo
43        use paramet_m, only: ip1jm, ip1jmp1
44        use phyredem_m, only: phyredem
45      use pressure_var, only: pls, p3d      use pressure_var, only: pls, p3d
46      use dynredem0_m, only: dynredem0      use q_sat_m, only: q_sat
47      use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz      use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz
48      use regr_pr_o3_m, only: regr_pr_o3      use regr_pr_o3_m, only: regr_pr_o3
49      use phyredem_m, only: phyredem      use serre, only: alphax
50        USE start_init_orog_m, only: start_init_orog, mask, phis
51        use start_init_phys_m, only: qsol_2d
52        use startdyn, only: start_inter_3d, start_init_dyn
53        use temps, only: itau_phy, annee_ref, day_ref
54    
55      ! Variables local to the procedure:      ! Variables local to the procedure:
56    
# Line 105  contains Line 108  contains
108      REAL pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)      REAL pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)
109      REAL w(ip1jmp1, llm)      REAL w(ip1jmp1, llm)
110      REAL phystep      REAL phystep
111        real trash
112    
113      !---------------------------------      !---------------------------------
114    
# Line 147  contains Line 151  contains
151      PRINT *, "minval(pls(:, :, :)) = ", minval(pls(:, :, :))      PRINT *, "minval(pls(:, :, :)) = ", minval(pls(:, :, :))
152      print *, "maxval(pls(:, :, :)) = ", maxval(pls(:, :, :))      print *, "maxval(pls(:, :, :)) = ", maxval(pls(:, :, :))
153    
154      uvent(:, :, :) = start_inter_3d('U', rlonv, rlatv, pls)      call start_inter_3d('U', rlonv, rlatv, pls, uvent)
155      forall (l = 1: llm) uvent(:iim, :, l) = uvent(:iim, :, l) * cu_2d(:iim, :)      forall (l = 1: llm) uvent(:iim, :, l) = uvent(:iim, :, l) * cu_2d(:iim, :)
156      uvent(iim+1, :, :) = uvent(1, :, :)      uvent(iim+1, :, :) = uvent(1, :, :)
157    
158      vvent(:, :, :) = start_inter_3d('V', rlonu, rlatu(:jjm), pls(:, :jjm, :))      call start_inter_3d('V', rlonu, rlatu(:jjm), pls(:, :jjm, :), vvent)
159      forall (l = 1: llm) vvent(:iim, :, l) = vvent(:iim, :, l) * cv_2d(:iim, :)      forall (l = 1: llm) vvent(:iim, :, l) = vvent(:iim, :, l) * cv_2d(:iim, :)
160      vvent(iim + 1, :, :) = vvent(1, :, :)      vvent(iim + 1, :, :) = vvent(1, :, :)
161    
162      t3d(:, :, :) = start_inter_3d('TEMP', rlonu, rlatv, pls)      call start_inter_3d('TEMP', rlonu, rlatv, pls, t3d)
163      PRINT *,  'minval(t3d(:, :, :)) = ', minval(t3d(:, :, :))      PRINT *,  'minval(t3d(:, :, :)) = ', minval(t3d(:, :, :))
164      print *, "maxval(t3d(:, :, :)) = ", maxval(t3d(:, :, :))      print *, "maxval(t3d(:, :, :)) = ", maxval(t3d(:, :, :))
165    
# Line 174  contains Line 178  contains
178      IF (MINVAL(qsat) == MAXVAL(qsat)) stop '"qsat" should not be constant'      IF (MINVAL(qsat) == MAXVAL(qsat)) stop '"qsat" should not be constant'
179    
180      ! Water vapor:      ! Water vapor:
181      q3d(:, :, :, 1) = 0.01 * start_inter_3d('R', rlonu, rlatv, pls) * qsat      call start_inter_3d('R', rlonu, rlatv, pls, q3d(:, :, :, 1))
182        q3d(:, :, :, 1) = 0.01 * q3d(:, :, :, 1) * qsat
183      WHERE (q3d(:, :, :, 1) < 0.) q3d(:, :, :, 1) = 1E-10      WHERE (q3d(:, :, :, 1) < 0.) q3d(:, :, :, 1) = 1E-10
184      DO l = 1, llm      DO l = 1, llm
185         q3d(:, 1, l, 1) = SUM(aire_2d(:, 1) * q3d(:, 1, l, 1)) / apoln         q3d(:, 1, l, 1) = SUM(aire_2d(:, 1) * q3d(:, 1, l, 1)) / apoln
# Line 217  contains Line 222  contains
222      ALLOCATE(dlon_lic(iml_lic))      ALLOCATE(dlon_lic(iml_lic))
223      ALLOCATE(dlat_lic(jml_lic))      ALLOCATE(dlat_lic(jml_lic))
224      ALLOCATE(fraclic(iml_lic, jml_lic))      ALLOCATE(fraclic(iml_lic, jml_lic))
225      CALL flinopen_nozoom("landiceref.nc", iml_lic, jml_lic, &      CALL flinopen_nozoom(iml_lic, jml_lic, &
226           llm_tmp, lon_lic, lat_lic, lev, ttm_tmp, itaul, date, dt,  &           llm_tmp, lon_lic, lat_lic, lev, ttm_tmp, itaul, date, trash,  &
227           fid)           fid)
228      CALL flinget(fid, 'landice', iml_lic, jml_lic, llm_tmp, ttm_tmp &      CALL flinget(fid, 'landice', iml_lic, jml_lic, llm_tmp, ttm_tmp &
229           , 1, 1, fraclic)           , 1, 1, fraclic)
# Line 288  contains Line 293  contains
293    
294      ! Initialisation pour traceurs:      ! Initialisation pour traceurs:
295      call iniadvtrac      call iniadvtrac
296      ! Ecriture:      CALL inidissip
     CALL inidissip(lstardis, nitergdiv, nitergrot, niterh, tetagdiv, &  
          tetagrot, tetatemp)  
     itau_dyn = 0  
297      itau_phy = 0      itau_phy = 0
298      day_ref = dayref      day_ref = dayref
299      annee_ref = anneeref      annee_ref = anneeref
300    
301      CALL geopot(ip1jmp1, tpot, pk , pks,  phis  , phi)      CALL geopot(ip1jmp1, tpot, pk , pks,  phis, phi)
302      CALL caldyn0(0, uvent, vvent, tpot, psol, masse, pk, phis, phi, w, &      CALL caldyn0(uvent, vvent, tpot, psol, masse, pk, phis, phi, w, pbaru, &
303           pbaru, pbarv, 0)           pbarv)
304      CALL dynredem0("start.nc", dayref, phis)      CALL dynredem0("start.nc", dayref, phis)
305      CALL dynredem1("start.nc", 0., vvent, uvent, tpot, q3d, masse, psol)      CALL dynredem1("start.nc", vvent, uvent, tpot, q3d, masse, psol, itau=0)
306    
307      ! Ecriture état initial physique:      ! Ecriture état initial physique:
     print *, 'dtvr = ', dtvr  
308      print *, "iphysiq = ", iphysiq      print *, "iphysiq = ", iphysiq
309      phystep   = dtvr * REAL(iphysiq)      phystep   = dtvr * REAL(iphysiq)
310      print *, 'phystep = ', phystep      print *, 'phystep = ', phystep

Legend:
Removed from v.18  
changed lines
  Added in v.32

  ViewVC Help
Powered by ViewVC 1.1.21