/[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 5 by guez, Mon Mar 3 16:32:04 2008 UTC revision 15 by guez, Fri Aug 1 15:24:12 2008 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 36  contains Line 38  contains
38      use serre, only: alphax      use serre, only: alphax
39      use dimsoil, only: nsoilmx      use dimsoil, only: nsoilmx
40      use temps, only: itau_dyn, itau_phy, annee_ref, day_ref, dt      use temps, only: itau_dyn, itau_phy, annee_ref, day_ref, dt
     use clesphys, only: ok_orodr, nbapp_rad  
41      use grid_atob, only: grille_m      use grid_atob, only: grille_m
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
     use regr_coefoz_m, only: regr_coefoz  
45      use advtrac_m, only: iniadvtrac      use advtrac_m, only: iniadvtrac
46      use netcdf95, only: nf95_open, nf95_close, nf95_inq_varid, nf90_nowrite, &      use pressure_var, only: pls, p3d
47           nf90_get_var, handle_err      use dynredem0_m, only: dynredem0
48      use pressure_m, only: pls, p3d      use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz
49        use regr_pr_o3_m, only: regr_pr_o3
50        use phyredem_m, only: phyredem
51    
52      ! Variables local to the procedure:      ! Variables local to the procedure:
53    
# Line 81  contains Line 83  contains
83      REAL zsig(klon), zgam(klon)      REAL zsig(klon), zgam(klon)
84      REAL zthe(klon)      REAL zthe(klon)
85      REAL zpic(klon), zval(klon)      REAL zpic(klon), zval(klon)
     REAL rugsrel(klon)  
86      REAL t_ancien(klon, llm), q_ancien(klon, llm)      !      REAL t_ancien(klon, llm), q_ancien(klon, llm)      !
87      REAL run_off_lic_0(klon)      REAL run_off_lic_0(klon)
88      real clwcon(klon, llm), rnebcon(klon, llm), ratqs(klon, llm)      real clwcon(klon, llm), rnebcon(klon, llm), ratqs(klon, llm)
# Line 104  contains Line 105  contains
105      REAL pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)      REAL pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)
106      REAL w(ip1jmp1, llm)      REAL w(ip1jmp1, llm)
107      REAL phystep      REAL phystep
     INTEGER radpas  
     integer ncid, varid, ncerr, month  
108    
109      !---------------------------------      !---------------------------------
110    
# Line 132  contains Line 131  contains
131      lonfi(klon) = 0.      lonfi(klon) = 0.
132    
133      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, &
134           zval_2d) ! also compute "masque" and "phis"           zval_2d) ! also compute "mask" and "phis"
135      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
136      zmasq = pack(masque, dyn_phy)      zmasq = pack(mask, dyn_phy)
137      PRINT *, 'Masque construit'      PRINT *, 'Masque construit'
138    
139      CALL start_init_dyn(tsol_2d, psol) ! also compute "qsol_2d"      CALL start_init_dyn(tsol_2d, psol) ! also compute "qsol_2d"
140    
141      ! Compute pressure on intermediate levels:      ! Compute pressure on intermediate levels:
142      forall(l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * psol(:, :)      forall(l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * psol
143      CALL exner_hyb(psol, p3d, pks, pk)      CALL exner_hyb(psol, p3d, pks, pk)
144      IF (MINVAL(pk) == MAXVAL(pk)) stop '"pk" should not be constant'      IF (MINVAL(pk) == MAXVAL(pk)) stop '"pk" should not be constant'
145    
# Line 187  contains Line 186  contains
186    
187      if (nqmx >= 5) then      if (nqmx >= 5) then
188         ! Ozone:         ! Ozone:
189           call regr_lat_time_coefoz
190         ! Compute ozone parameters on the LMDZ grid:         call regr_pr_o3(q3d(:, :, :, 5))
191         call regr_coefoz         ! Convert from mole fraction to mass fraction:
192           q3d(:, :, :, 5) = q3d(:, :, :, 5)  * 48. / 29.
        ! Find the month containing the day number "dayref":  
        month = (dayref - 1) / 30 + 1  
        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.  
193      end if      end if
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)
197      sn(:) = 0. ! snow      sn = 0. ! snow
198      radsol(:) = 0.      radsol = 0.
199      tslab(:) = 0. ! IM "slab" ocean      tslab = 0. ! IM "slab" ocean
200      seaice(:) = 0.      seaice = 0.
201      rugmer(:) = 0.001      rugmer = 0.001
202      zmea(:) = pack(relief, dyn_phy)      zmea = pack(relief, dyn_phy)
203      zstd(:) = pack(zstd_2d, dyn_phy)      zstd = pack(zstd_2d, dyn_phy)
204      zsig(:) = pack(zsig_2d, dyn_phy)      zsig = pack(zsig_2d, dyn_phy)
205      zgam(:) = pack(zgam_2d, dyn_phy)      zgam = pack(zgam_2d, dyn_phy)
206      zthe(:) = pack(zthe_2d, dyn_phy)      zthe = pack(zthe_2d, dyn_phy)
207      zpic(:) = pack(zpic_2d, dyn_phy)      zpic = pack(zpic_2d, dyn_phy)
208      zval(:) = pack(zval_2d, dyn_phy)      zval = pack(zval_2d, dyn_phy)
   
     rugsrel(:) = 0.  
     IF (ok_orodr) rugsrel(:) = MAX(1.e-05, zstd(:) * zsig(:) / 2)  
209    
210      ! On initialise les sous-surfaces:      ! On initialise les sous-surfaces:
211      ! Lecture du fichier glace de terre pour fixer la fraction de terre      ! Lecture du fichier glace de terre pour fixer la fraction de terre
# Line 251  contains Line 230  contains
230      print *, "jml_lic = ", jml_lic      print *, "jml_lic = ", jml_lic
231    
232      ! Si les coordonnées sont en degrés, on les transforme :      ! Si les coordonnées sont en degrés, on les transforme :
233      IF (MAXVAL( lon_lic(:, :) ) > pi)  THEN      IF (MAXVAL( lon_lic ) > pi)  THEN
234         lon_lic(:, :) = lon_lic(:, :) * pi / 180.         lon_lic = lon_lic * pi / 180.
235      ENDIF      ENDIF
236      IF (maxval( lat_lic(:, :) ) > pi) THEN      IF (maxval( lat_lic ) > pi) THEN
237         lat_lic(:, :) = lat_lic(:, :) * pi/ 180.         lat_lic = lat_lic * pi/ 180.
238      ENDIF      ENDIF
239    
240      dlon_lic(:) = lon_lic(:, 1)      dlon_lic = lon_lic(:, 1)
241      dlat_lic(:) = lat_lic(1, :)      dlat_lic = lat_lic(1, :)
242    
243      flic_tmp(:iim, :) = grille_m(dlon_lic, dlat_lic, fraclic, rlonv(:iim), &      flic_tmp(:iim, :) = grille_m(dlon_lic, dlat_lic, fraclic, rlonv(:iim), &
244           rlatu)           rlatu)
245      flic_tmp(iim + 1, :) = flic_tmp(1, :)      flic_tmp(iim + 1, :) = flic_tmp(1, :)
246    
247      ! Passage sur la grille physique      ! Passage sur la grille physique
248      pctsrf(:, :)=0.      pctsrf = 0.
249      pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy)      pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy)
250      ! Adéquation avec le maque terre/mer      ! Adéquation avec le maque terre/mer
251      WHERE (pctsrf(:, is_lic) < EPSFRA ) pctsrf(:, is_lic) = 0.      WHERE (pctsrf(:, is_lic) < EPSFRA ) pctsrf(:, is_lic) = 0.
252      WHERE (zmasq(:) < EPSFRA) pctsrf(:, is_lic) = 0.      WHERE (zmasq < EPSFRA) pctsrf(:, is_lic) = 0.
253      pctsrf(:, is_ter) = zmasq(:)      pctsrf(:, is_ter) = zmasq
254      where (zmasq(:) > EPSFRA)      where (zmasq > EPSFRA)
255         where (pctsrf(:, is_lic) >= zmasq(:))         where (pctsrf(:, is_lic) >= zmasq)
256            pctsrf(:, is_lic) = zmasq(:)            pctsrf(:, is_lic) = zmasq
257            pctsrf(:, is_ter) = 0.            pctsrf(:, is_ter) = 0.
258         elsewhere         elsewhere
259            pctsrf(:, is_ter) = zmasq(:) - pctsrf(:, is_lic)            pctsrf(:, is_ter) = zmasq - pctsrf(:, is_lic)
260            where (pctsrf(:, is_ter) < EPSFRA)            where (pctsrf(:, is_ter) < EPSFRA)
261               pctsrf(:, is_ter) = 0.               pctsrf(:, is_ter) = 0.
262               pctsrf(:, is_lic) = zmasq(:)               pctsrf(:, is_lic) = zmasq
263            end where            end where
264         end where         end where
265      end where      end where
266    
267      ! Sous-surface océan et glace de mer (pour démarrer on met glace      ! Sous-surface océan et glace de mer (pour démarrer on met glace
268      ! de mer à 0) :      ! de mer à 0) :
269      pctsrf(:, is_oce) = 1. - zmasq(:)      pctsrf(:, is_oce) = 1. - zmasq
270      WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0.      WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0.
271    
272      ! Vérification que somme des sous-surfaces vaut 1:      ! Vérification que somme des sous-surfaces vaut 1:
273      ji = count(abs(sum(pctsrf(:, :), dim = 2) - 1. ) > EPSFRA)      ji = count(abs(sum(pctsrf, dim = 2) - 1.) > EPSFRA)
274      IF (ji /= 0) PRINT *, 'Problème répartition sous maille pour', ji, 'points'      IF (ji /= 0) then
275           PRINT *, 'Problème répartition sous maille pour ', ji, 'points'
276        end IF
277    
278      ! Calcul intermédiaire:      ! Calcul intermédiaire:
279      CALL massdair(p3d, masse)      CALL massdair(p3d, masse)
# Line 324  contains Line 305  contains
305      ! Ecriture état initial physique:      ! Ecriture état initial physique:
306      print *, 'dtvr = ', dtvr      print *, 'dtvr = ', dtvr
307      print *, "iphysiq = ", iphysiq      print *, "iphysiq = ", iphysiq
     print *, "nbapp_rad = ", nbapp_rad  
308      phystep   = dtvr * REAL(iphysiq)      phystep   = dtvr * REAL(iphysiq)
     radpas    = NINT (86400./phystep/ nbapp_rad)  
309      print *, 'phystep = ', phystep      print *, 'phystep = ', phystep
     print *, "radpas = ", radpas  
310    
311      ! Initialisations :      ! Initialisations :
312      tsolsrf(:, is_ter) = tsol      tsolsrf(:, is_ter) = tsol
# Line 344  contains Line 322  contains
322      albe(:, is_oce) = 0.5      albe(:, is_oce) = 0.5
323      albe(:, is_sic) = 0.6      albe(:, is_sic) = 0.6
324      alblw = albe      alblw = albe
325      evap(:, :) = 0.      evap = 0.
326      qsolsrf(:, is_ter) = 150.      qsolsrf(:, is_ter) = 150.
327      qsolsrf(:, is_lic) = 150.      qsolsrf(:, is_lic) = 150.
328      qsolsrf(:, is_oce) = 150.      qsolsrf(:, is_oce) = 150.
# Line 358  contains Line 336  contains
336      q_ancien = 0.      q_ancien = 0.
337      agesno = 0.      agesno = 0.
338      !IM "slab" ocean      !IM "slab" ocean
339      tslab(:) = tsolsrf(:, is_oce)      tslab = tsolsrf(:, is_oce)
340      seaice = 0.      seaice = 0.
341    
342      frugs(:, is_oce) = rugmer(:)      frugs(:, is_oce) = rugmer
343      frugs(:, is_ter) = MAX(1.e-05, zstd(:) * zsig(:) / 2)      frugs(:, is_ter) = MAX(1.e-05, zstd * zsig / 2)
344      frugs(:, is_lic) = MAX(1.e-05, zstd(:) * zsig(:) / 2)      frugs(:, is_lic) = MAX(1.e-05, zstd * zsig / 2)
345      frugs(:, is_sic) = 0.001      frugs(:, is_sic) = 0.001
346      fder = 0.      fder = 0.
347      clwcon = 0.      clwcon = 0.
# Line 371  contains Line 349  contains
349      ratqs = 0.      ratqs = 0.
350      run_off_lic_0 = 0.      run_off_lic_0 = 0.
351    
352      call phyredem("startphy.nc", phystep, radpas, latfi, lonfi, pctsrf, &      call phyredem("startphy.nc", latfi, lonfi, pctsrf, &
353           tsolsrf, tsoil, tslab, seaice, qsolsrf, qsol, snsrf, albe, alblw, &           tsolsrf, tsoil, tslab, seaice, qsolsrf, qsol, snsrf, albe, alblw, &
354           evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, frugs, &           evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, frugs, &
355           agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, rugsrel, &           agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &
356           t_ancien, q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0)           t_ancien, q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0)
357      CALL histclo      CALL histclo
358    

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

  ViewVC Help
Powered by ViewVC 1.1.21