/[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 3 by guez, Wed Feb 27 13:16:39 2008 UTC revision 12 by guez, Mon Jul 21 16:05:07 2008 UTC
# Line 36  contains Line 36  contains
36      use serre, only: alphax      use serre, only: alphax
37      use dimsoil, only: nsoilmx      use dimsoil, only: nsoilmx
38      use temps, only: itau_dyn, itau_phy, annee_ref, day_ref, dt      use temps, only: itau_dyn, itau_phy, annee_ref, day_ref, dt
39      use clesphys, only: ok_orodr, nbapp_rad      use clesphys2, only: ok_orodr, nbapp_rad
40      use grid_atob, only: grille_m      use grid_atob, only: grille_m
41      use grid_change, only: init_dyn_phy, dyn_phy      use grid_change, only: init_dyn_phy, dyn_phy
42      use q_sat_m, only: q_sat      use q_sat_m, only: q_sat
43      use exner_hyb_m, only: exner_hyb      use exner_hyb_m, only: exner_hyb
     use regr_coefoz_m, only: regr_coefoz  
44      use advtrac_m, only: iniadvtrac      use advtrac_m, only: iniadvtrac
45      use netcdf95, only: nf95_open, nf95_close, nf95_inq_varid, nf90_nowrite, &      use pressure_var, only: pls, p3d
46           nf90_get_var, handle_err      use dynredem0_m, only: dynredem0
47      use pressure_m, only: pls, p3d      use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz
48        use regr_pr_o3_m, only: regr_pr_o3
49    
50      ! Variables local to the procedure:      ! Variables local to the procedure:
51    
# Line 95  contains Line 95  contains
95      REAL flic_tmp(iim + 1, jjm + 1) !fraction land ice temporary      REAL flic_tmp(iim + 1, jjm + 1) !fraction land ice temporary
96    
97      INTEGER l, ji      INTEGER l, ji
     INTEGER nq  
98    
99      REAL pk(iim + 1, jjm + 1, llm) ! fonction d'Exner aux milieux des couches      REAL pk(iim + 1, jjm + 1, llm) ! fonction d'Exner aux milieux des couches
100      real pks(iim + 1, jjm + 1)      real pks(iim + 1, jjm + 1)
# Line 106  contains Line 105  contains
105      REAL w(ip1jmp1, llm)      REAL w(ip1jmp1, llm)
106      REAL phystep      REAL phystep
107      INTEGER radpas      INTEGER radpas
     integer ncid, varid, ncerr, month  
108    
109      !---------------------------------      !---------------------------------
110    
# Line 186  contains Line 184  contains
184    
185      q3d(:, :, :, 2:4) = 0. ! liquid water, radon and lead      q3d(:, :, :, 2:4) = 0. ! liquid water, radon and lead
186    
187      ! Ozone:      if (nqmx >= 5) then
188           ! Ozone:
189      ! Compute ozone parameters on the LMDZ grid:         call regr_lat_time_coefoz
190      call regr_coefoz         call regr_pr_o3(q3d(:, :, :, 5))
191           ! Convert from mole fraction to mass fraction:
192      ! Find the month containing the day number "dayref":         q3d(:, :, :, 5) = q3d(:, :, :, 5)  * 48. / 29.
193      month = (dayref - 1) / 30 + 1      end if
     print *, "month = ", month  
   
     call nf95_open("coefoz_LMDZ.nc", nf90_nowrite, ncid)  
   
     ! Get data at the right month from the input file:  
     call nf95_inq_varid(ncid, "r_Mob", varid)  
     ncerr = nf90_get_var(ncid, varid, q3d(:, :, :, 5), &  
          start=(/1, 1, 1, month/))  
     call handle_err("nf90_get_var r_Mob", ncerr)  
   
     call nf95_close(ncid)  
     ! Latitudes are in increasing order in the input file while  
     ! "rlatu" is in decreasing order so we need to invert order. Also, we  
     ! compute mass fraction from mole fraction:  
     q3d(:, :, :, 5) = q3d(:, jjm+1:1:-1, :, 5)  * 48. / 29.  
194    
195      tsol(:) = pack(tsol_2d, dyn_phy)      tsol(:) = pack(tsol_2d, dyn_phy)
196      qsol(:) = pack(qsol_2d, dyn_phy)      qsol(:) = pack(qsol_2d, dyn_phy)
# Line 305  contains Line 288  contains
288      END forall      END forall
289    
290      ! Initialisation pour traceurs:      ! Initialisation pour traceurs:
291      call iniadvtrac(nq)      call iniadvtrac
292      ! Ecriture:      ! Ecriture:
293      CALL inidissip(lstardis, nitergdiv, nitergrot, niterh, tetagdiv, &      CALL inidissip(lstardis, nitergdiv, nitergrot, niterh, tetagdiv, &
294           tetagrot, tetatemp)           tetagrot, tetatemp)
# Line 317  contains Line 300  contains
300      CALL geopot(ip1jmp1, tpot, pk , pks,  phis  , phi)      CALL geopot(ip1jmp1, tpot, pk , pks,  phis  , phi)
301      CALL caldyn0(0, uvent, vvent, tpot, psol, masse, pk, phis, phi, w, &      CALL caldyn0(0, uvent, vvent, tpot, psol, masse, pk, phis, phi, w, &
302           pbaru, pbarv, 0)           pbaru, pbarv, 0)
303      CALL dynredem0("start.nc", dayref, phis, nqmx)      CALL dynredem0("start.nc", dayref, phis)
304      CALL dynredem1("start.nc", 0., vvent, uvent, tpot, q3d, nqmx, masse, psol)      CALL dynredem1("start.nc", 0., vvent, uvent, tpot, q3d, masse, psol)
305    
306      ! Ecriture état initial physique:      ! Ecriture état initial physique:
307      print *, 'dtvr = ', dtvr      print *, 'dtvr = ', dtvr
# Line 370  contains Line 353  contains
353      ratqs = 0.      ratqs = 0.
354      run_off_lic_0 = 0.      run_off_lic_0 = 0.
355    
356      call phyredem("startphy.nc", phystep, radpas, latfi, lonfi, pctsrf, &      call phyredem("startphy.nc", radpas, latfi, lonfi, pctsrf, &
357           tsolsrf, tsoil, tslab, seaice, qsolsrf, qsol, snsrf, albe, alblw, &           tsolsrf, tsoil, tslab, seaice, qsolsrf, qsol, snsrf, albe, alblw, &
358           evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, frugs, &           evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, frugs, &
359           agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, rugsrel, &           agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, rugsrel, &

Legend:
Removed from v.3  
changed lines
  Added in v.12

  ViewVC Help
Powered by ViewVC 1.1.21