/[lmdze]/trunk/dyn3d/etat0.f
ViewVC logotype

Diff of /trunk/dyn3d/etat0.f

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

revision 13 by guez, Fri Jul 25 19:59:34 2008 UTC revision 26 by guez, Tue Mar 9 15:27:15 2010 UTC
# Line 6  module etat0_mod Line 6  module etat0_mod
6    IMPLICIT NONE    IMPLICIT NONE
7    
8    REAL pctsrf(klon, nbsrf)    REAL pctsrf(klon, nbsrf)
9      ! ("pctsrf(i, :)" is the composition of the surface at horizontal
10      !  position "i")
11    
12    private nbsrf, klon    private nbsrf, klon
13    
# Line 15  contains Line 17  contains
17    
18      ! From "etat0_netcdf.F", version 1.3 2005/05/25 13:10:09      ! From "etat0_netcdf.F", version 1.3 2005/05/25 13:10:09
19    
20      ! This subroutine creates "masque".      ! This subroutine creates "mask".
21    
22      USE ioipsl, only: flinget, flinclo, flinopen_nozoom, flininfo, histclo      USE ioipsl, only: flinget, flinclo, flinopen_nozoom, flininfo, histclo
23    
24      USE start_init_orog_m, only: start_init_orog, masque, phis      USE start_init_orog_m, only: start_init_orog, mask, phis
25      use start_init_phys_m, only: qsol_2d      use start_init_phys_m, only: qsol_2d
26      use startdyn, only: start_inter_3d, start_init_dyn      use startdyn, only: start_inter_3d, start_init_dyn
27      use dimens_m, only: iim, jjm, llm, nqmx      use dimens_m, only: iim, jjm, llm, nqmx
# Line 40  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
51        use caldyn0_m, only: caldyn0
52        use inigeom_m, only: inigeom
53        use inidissip_m, only: inidissip
54    
55      ! Variables local to the procedure:      ! Variables local to the procedure:
56    
# Line 128  contains Line 134  contains
134      lonfi(klon) = 0.      lonfi(klon) = 0.
135    
136      call start_init_orog(relief, zstd_2d, zsig_2d, zgam_2d, zthe_2d, zpic_2d, &      call start_init_orog(relief, zstd_2d, zsig_2d, zgam_2d, zthe_2d, zpic_2d, &
137           zval_2d) ! also compute "masque" and "phis"           zval_2d) ! also compute "mask" and "phis"
138      call init_dyn_phy ! define the mask "dyn_phy" for distinct grid points      call init_dyn_phy ! define the mask "dyn_phy" for distinct grid points
139      zmasq = pack(masque, dyn_phy)      zmasq = pack(mask, dyn_phy)
140      PRINT *, 'Masque construit'      PRINT *, 'Masque construit'
141    
142      CALL start_init_dyn(tsol_2d, psol) ! also compute "qsol_2d"      CALL start_init_dyn(tsol_2d, psol) ! also compute "qsol_2d"
143    
144      ! Compute pressure on intermediate levels:      ! Compute pressure on intermediate levels:
145      forall(l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * psol(:, :)      forall(l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * psol
146      CALL exner_hyb(psol, p3d, pks, pk)      CALL exner_hyb(psol, p3d, pks, pk)
147      IF (MINVAL(pk) == MAXVAL(pk)) stop '"pk" should not be constant'      IF (MINVAL(pk) == MAXVAL(pk)) stop '"pk" should not be constant'
148    
# Line 144  contains Line 150  contains
150      PRINT *, "minval(pls(:, :, :)) = ", minval(pls(:, :, :))      PRINT *, "minval(pls(:, :, :)) = ", minval(pls(:, :, :))
151      print *, "maxval(pls(:, :, :)) = ", maxval(pls(:, :, :))      print *, "maxval(pls(:, :, :)) = ", maxval(pls(:, :, :))
152    
153      uvent(:, :, :) = start_inter_3d('U', rlonv, rlatv, pls)      call start_inter_3d('U', rlonv, rlatv, pls, uvent)
154      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, :)
155      uvent(iim+1, :, :) = uvent(1, :, :)      uvent(iim+1, :, :) = uvent(1, :, :)
156    
157      vvent(:, :, :) = start_inter_3d('V', rlonu, rlatu(:jjm), pls(:, :jjm, :))      call start_inter_3d('V', rlonu, rlatu(:jjm), pls(:, :jjm, :), vvent)
158      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, :)
159      vvent(iim + 1, :, :) = vvent(1, :, :)      vvent(iim + 1, :, :) = vvent(1, :, :)
160    
161      t3d(:, :, :) = start_inter_3d('TEMP', rlonu, rlatv, pls)      call start_inter_3d('TEMP', rlonu, rlatv, pls, t3d)
162      PRINT *,  'minval(t3d(:, :, :)) = ', minval(t3d(:, :, :))      PRINT *,  'minval(t3d(:, :, :)) = ', minval(t3d(:, :, :))
163      print *, "maxval(t3d(:, :, :)) = ", maxval(t3d(:, :, :))      print *, "maxval(t3d(:, :, :)) = ", maxval(t3d(:, :, :))
164    
# Line 171  contains Line 177  contains
177      IF (MINVAL(qsat) == MAXVAL(qsat)) stop '"qsat" should not be constant'      IF (MINVAL(qsat) == MAXVAL(qsat)) stop '"qsat" should not be constant'
178    
179      ! Water vapor:      ! Water vapor:
180      q3d(:, :, :, 1) = 0.01 * start_inter_3d('R', rlonu, rlatv, pls) * qsat      call start_inter_3d('R', rlonu, rlatv, pls, q3d(:, :, :, 1))
181        q3d(:, :, :, 1) = 0.01 * q3d(:, :, :, 1) * qsat
182      WHERE (q3d(:, :, :, 1) < 0.) q3d(:, :, :, 1) = 1E-10      WHERE (q3d(:, :, :, 1) < 0.) q3d(:, :, :, 1) = 1E-10
183      DO l = 1, llm      DO l = 1, llm
184         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 227  contains Line 234  contains
234      print *, "jml_lic = ", jml_lic      print *, "jml_lic = ", jml_lic
235    
236      ! Si les coordonnées sont en degrés, on les transforme :      ! Si les coordonnées sont en degrés, on les transforme :
237      IF (MAXVAL( lon_lic(:, :) ) > pi)  THEN      IF (MAXVAL( lon_lic ) > pi)  THEN
238         lon_lic(:, :) = lon_lic(:, :) * pi / 180.         lon_lic = lon_lic * pi / 180.
239      ENDIF      ENDIF
240      IF (maxval( lat_lic(:, :) ) > pi) THEN      IF (maxval( lat_lic ) > pi) THEN
241         lat_lic(:, :) = lat_lic(:, :) * pi/ 180.         lat_lic = lat_lic * pi/ 180.
242      ENDIF      ENDIF
243    
244      dlon_lic = lon_lic(:, 1)      dlon_lic = lon_lic(:, 1)
# Line 242  contains Line 249  contains
249      flic_tmp(iim + 1, :) = flic_tmp(1, :)      flic_tmp(iim + 1, :) = flic_tmp(1, :)
250    
251      ! Passage sur la grille physique      ! Passage sur la grille physique
252      pctsrf(:, :)=0.      pctsrf = 0.
253      pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy)      pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy)
254      ! Adéquation avec le maque terre/mer      ! Adéquation avec le maque terre/mer
255      WHERE (pctsrf(:, is_lic) < EPSFRA ) pctsrf(:, is_lic) = 0.      WHERE (pctsrf(:, is_lic) < EPSFRA ) pctsrf(:, is_lic) = 0.
# Line 267  contains Line 274  contains
274      WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0.      WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0.
275    
276      ! Vérification que somme des sous-surfaces vaut 1:      ! Vérification que somme des sous-surfaces vaut 1:
277      ji = count(abs(sum(pctsrf(:, :), dim = 2) - 1. ) > EPSFRA)      ji = count(abs(sum(pctsrf, dim = 2) - 1.) > EPSFRA)
278      IF (ji /= 0) PRINT *, 'Problème répartition sous maille pour', ji, 'points'      IF (ji /= 0) then
279           PRINT *, 'Problème répartition sous maille pour ', ji, 'points'
280        end IF
281    
282      ! Calcul intermédiaire:      ! Calcul intermédiaire:
283      CALL massdair(p3d, masse)      CALL massdair(p3d, masse)
# Line 283  contains Line 292  contains
292    
293      ! Initialisation pour traceurs:      ! Initialisation pour traceurs:
294      call iniadvtrac      call iniadvtrac
     ! Ecriture:  
295      CALL inidissip(lstardis, nitergdiv, nitergrot, niterh, tetagdiv, &      CALL inidissip(lstardis, nitergdiv, nitergrot, niterh, tetagdiv, &
296           tetagrot, tetatemp)           tetagrot, tetatemp)
297      itau_dyn = 0      itau_dyn = 0
# Line 291  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
# Line 317  contains Line 324  contains
324      albe(:, is_oce) = 0.5      albe(:, is_oce) = 0.5
325      albe(:, is_sic) = 0.6      albe(:, is_sic) = 0.6
326      alblw = albe      alblw = albe
327      evap(:, :) = 0.      evap = 0.
328      qsolsrf(:, is_ter) = 150.      qsolsrf(:, is_ter) = 150.
329      qsolsrf(:, is_lic) = 150.      qsolsrf(:, is_lic) = 150.
330      qsolsrf(:, is_oce) = 150.      qsolsrf(:, is_oce) = 150.

Legend:
Removed from v.13  
changed lines
  Added in v.26

  ViewVC Help
Powered by ViewVC 1.1.21