/[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 15 by guez, Fri Aug 1 15:24:12 2008 UTC revision 25 by guez, Fri Mar 5 16:43:45 2010 UTC
# Line 42  contains Line 42  contains
42      use grid_change, only: init_dyn_phy, dyn_phy      use grid_change, only: init_dyn_phy, dyn_phy
43      use q_sat_m, only: q_sat      use q_sat_m, only: q_sat
44      use exner_hyb_m, only: exner_hyb      use exner_hyb_m, only: exner_hyb
45      use advtrac_m, only: iniadvtrac      use iniadvtrac_m, only: iniadvtrac
46      use pressure_var, only: pls, p3d      use pressure_var, only: pls, p3d
47      use dynredem0_m, only: dynredem0      use dynredem0_m, only: dynredem0
48      use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz      use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz
49      use regr_pr_o3_m, only: regr_pr_o3      use regr_pr_o3_m, only: regr_pr_o3
50      use phyredem_m, only: phyredem      use phyredem_m, only: phyredem
51        use caldyn0_m, only: caldyn0
52        use inigeom_m, only: inigeom
53    
54      ! Variables local to the procedure:      ! Variables local to the procedure:
55    
# Line 147  contains Line 149  contains
149      PRINT *, "minval(pls(:, :, :)) = ", minval(pls(:, :, :))      PRINT *, "minval(pls(:, :, :)) = ", minval(pls(:, :, :))
150      print *, "maxval(pls(:, :, :)) = ", maxval(pls(:, :, :))      print *, "maxval(pls(:, :, :)) = ", maxval(pls(:, :, :))
151    
152      uvent(:, :, :) = start_inter_3d('U', rlonv, rlatv, pls)      call start_inter_3d('U', rlonv, rlatv, pls, uvent)
153      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, :)
154      uvent(iim+1, :, :) = uvent(1, :, :)      uvent(iim+1, :, :) = uvent(1, :, :)
155    
156      vvent(:, :, :) = start_inter_3d('V', rlonu, rlatu(:jjm), pls(:, :jjm, :))      call start_inter_3d('V', rlonu, rlatu(:jjm), pls(:, :jjm, :), vvent)
157      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, :)
158      vvent(iim + 1, :, :) = vvent(1, :, :)      vvent(iim + 1, :, :) = vvent(1, :, :)
159    
160      t3d(:, :, :) = start_inter_3d('TEMP', rlonu, rlatv, pls)      call start_inter_3d('TEMP', rlonu, rlatv, pls, t3d)
161      PRINT *,  'minval(t3d(:, :, :)) = ', minval(t3d(:, :, :))      PRINT *,  'minval(t3d(:, :, :)) = ', minval(t3d(:, :, :))
162      print *, "maxval(t3d(:, :, :)) = ", maxval(t3d(:, :, :))      print *, "maxval(t3d(:, :, :)) = ", maxval(t3d(:, :, :))
163    
# Line 174  contains Line 176  contains
176      IF (MINVAL(qsat) == MAXVAL(qsat)) stop '"qsat" should not be constant'      IF (MINVAL(qsat) == MAXVAL(qsat)) stop '"qsat" should not be constant'
177    
178      ! Water vapor:      ! Water vapor:
179      q3d(:, :, :, 1) = 0.01 * start_inter_3d('R', rlonu, rlatv, pls) * qsat      call start_inter_3d('R', rlonu, rlatv, pls, q3d(:, :, :, 1))
180        q3d(:, :, :, 1) = 0.01 * q3d(:, :, :, 1) * qsat
181      WHERE (q3d(:, :, :, 1) < 0.) q3d(:, :, :, 1) = 1E-10      WHERE (q3d(:, :, :, 1) < 0.) q3d(:, :, :, 1) = 1E-10
182      DO l = 1, llm      DO l = 1, llm
183         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 296  contains Line 299  contains
299      day_ref = dayref      day_ref = dayref
300      annee_ref = anneeref      annee_ref = anneeref
301    
302      CALL geopot(ip1jmp1, tpot, pk , pks,  phis  , phi)      CALL geopot(ip1jmp1, tpot, pk , pks,  phis, phi)
303      CALL caldyn0(0, uvent, vvent, tpot, psol, masse, pk, phis, phi, w, &      CALL caldyn0(uvent, vvent, tpot, psol, masse, pk, phis, phi, w, pbaru, &
304           pbaru, pbarv, 0)           pbarv)
305      CALL dynredem0("start.nc", dayref, phis)      CALL dynredem0("start.nc", dayref, phis)
306      CALL dynredem1("start.nc", 0., vvent, uvent, tpot, q3d, masse, psol)      CALL dynredem1("start.nc", vvent, uvent, tpot, q3d, masse, psol)
307    
308      ! Ecriture état initial physique:      ! Ecriture état initial physique:
     print *, 'dtvr = ', dtvr  
309      print *, "iphysiq = ", iphysiq      print *, "iphysiq = ", iphysiq
310      phystep   = dtvr * REAL(iphysiq)      phystep   = dtvr * REAL(iphysiq)
311      print *, 'phystep = ', phystep      print *, 'phystep = ', phystep

Legend:
Removed from v.15  
changed lines
  Added in v.25

  ViewVC Help
Powered by ViewVC 1.1.21