/[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 22 by guez, Fri Jul 31 15:18:47 2009 UTC revision 23 by guez, Mon Dec 14 15:25:16 2009 UTC
# Line 48  contains Line 48  contains
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    
53      ! Variables local to the procedure:      ! Variables local to the procedure:
54    
# Line 147  contains Line 148  contains
148      PRINT *, "minval(pls(:, :, :)) = ", minval(pls(:, :, :))      PRINT *, "minval(pls(:, :, :)) = ", minval(pls(:, :, :))
149      print *, "maxval(pls(:, :, :)) = ", maxval(pls(:, :, :))      print *, "maxval(pls(:, :, :)) = ", maxval(pls(:, :, :))
150    
151      uvent(:, :, :) = start_inter_3d('U', rlonv, rlatv, pls)      call start_inter_3d('U', rlonv, rlatv, pls, uvent)
152      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, :)
153      uvent(iim+1, :, :) = uvent(1, :, :)      uvent(iim+1, :, :) = uvent(1, :, :)
154    
155      vvent(:, :, :) = start_inter_3d('V', rlonu, rlatu(:jjm), pls(:, :jjm, :))      call start_inter_3d('V', rlonu, rlatu(:jjm), pls(:, :jjm, :), vvent)
156      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, :)
157      vvent(iim + 1, :, :) = vvent(1, :, :)      vvent(iim + 1, :, :) = vvent(1, :, :)
158    
159      t3d(:, :, :) = start_inter_3d('TEMP', rlonu, rlatv, pls)      call start_inter_3d('TEMP', rlonu, rlatv, pls, t3d)
160      PRINT *,  'minval(t3d(:, :, :)) = ', minval(t3d(:, :, :))      PRINT *,  'minval(t3d(:, :, :)) = ', minval(t3d(:, :, :))
161      print *, "maxval(t3d(:, :, :)) = ", maxval(t3d(:, :, :))      print *, "maxval(t3d(:, :, :)) = ", maxval(t3d(:, :, :))
162    
# Line 174  contains Line 175  contains
175      IF (MINVAL(qsat) == MAXVAL(qsat)) stop '"qsat" should not be constant'      IF (MINVAL(qsat) == MAXVAL(qsat)) stop '"qsat" should not be constant'
176    
177      ! Water vapor:      ! Water vapor:
178      q3d(:, :, :, 1) = 0.01 * start_inter_3d('R', rlonu, rlatv, pls) * qsat      call start_inter_3d('R', rlonu, rlatv, pls, q3d(:, :, :, 1))
179        q3d(:, :, :, 1) = 0.01 * q3d(:, :, :, 1) * qsat
180      WHERE (q3d(:, :, :, 1) < 0.) q3d(:, :, :, 1) = 1E-10      WHERE (q3d(:, :, :, 1) < 0.) q3d(:, :, :, 1) = 1E-10
181      DO l = 1, llm      DO l = 1, llm
182         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 297  contains Line 299  contains
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)
306    
307      ! Ecriture état initial physique:      ! Ecriture état initial physique:
308      print *, 'dtvr = ', dtvr      print *, 'dtvr = ', dtvr

Legend:
Removed from v.22  
changed lines
  Added in v.23

  ViewVC Help
Powered by ViewVC 1.1.21