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

Diff of /trunk/Sources/dyn3d/etat0.f

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

trunk/dyn3d/etat0.f90 revision 78 by guez, Wed Feb 5 17:51:07 2014 UTC trunk/dyn3d/etat0.f revision 113 by guez, Thu Sep 18 19:56:46 2014 UTC
# Line 13  module etat0_mod Line 13  module etat0_mod
13    
14  contains  contains
15    
16    SUBROUTINE etat0    SUBROUTINE etat0(phis)
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      use caldyn0_m, only: caldyn0      use caldyn0_m, only: caldyn0
21      use comconst, only: dtvr, daysec, cpp, kappa      use comconst, only: cpp, kappa, iniconst
22      use comgeom, only: rlatu, rlonv, rlonu, rlatv, aire_2d, apoln, apols, &      use comgeom, only: rlatu, rlonv, rlonu, rlatv, aire_2d, apoln, apols, &
23           cu_2d, cv_2d, inigeom           cu_2d, cv_2d, inigeom
24      use conf_gcm_m, only: day_step, iphysiq, dayref, anneeref      use conf_gcm_m, only: dayref, anneeref
25      use dimens_m, only: iim, jjm, llm, nqmx      use dimens_m, only: iim, jjm, llm, nqmx
26      use dimphy, only: zmasq      use dimphy, only: zmasq
27      use dimsoil, only: nsoilmx      use dimsoil, only: nsoilmx
28      use disvert_m, only: ap, bp, preff, pa      use disvert_m, only: ap, bp, preff, pa, disvert
29      use dynredem0_m, only: dynredem0      use dynredem0_m, only: dynredem0
30      use dynredem1_m, only: dynredem1      use dynredem1_m, only: dynredem1
31      use exner_hyb_m, only: exner_hyb      use exner_hyb_m, only: exner_hyb
# Line 40  contains Line 40  contains
40      use netcdf, only: nf90_nowrite      use netcdf, only: nf90_nowrite
41      use netcdf95, only: nf95_close, nf95_get_var, nf95_gw_var, &      use netcdf95, only: nf95_close, nf95_get_var, nf95_gw_var, &
42           nf95_inq_varid, nf95_open           nf95_inq_varid, nf95_open
43      use nr_util, only: pi      use nr_util, only: pi, assert
44      use paramet_m, only: ip1jm, ip1jmp1      use paramet_m, only: ip1jm, ip1jmp1
45      use phyredem_m, only: phyredem      use phyredem_m, only: phyredem
     use pressure_var, only: pls, p3d  
46      use q_sat_m, only: q_sat      use q_sat_m, only: q_sat
47      use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz      use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz
48      use regr_pr_o3_m, only: regr_pr_o3      use regr_pr_o3_m, only: regr_pr_o3
     use serre, only: alphax  
49      use startdyn, only: start_init_dyn      use startdyn, only: start_init_dyn
50      USE start_init_orog_m, only: start_init_orog, mask      USE start_init_orog_m, only: start_init_orog, mask
51      use start_init_phys_m, only: start_init_phys      use start_init_phys_m, only: start_init_phys
52      use start_inter_3d_m, only: start_inter_3d      use start_inter_3d_m, only: start_inter_3d
53      use temps, only: itau_phy, annee_ref, day_ref      use temps, only: itau_phy, annee_ref, day_ref
54        use test_disvert_m, only: test_disvert
55    
56      ! Variables local to the procedure:      REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)
57        ! surface geopotential, in m2 s-2
58    
59        ! Local:
60    
61      REAL latfi(klon), lonfi(klon)      REAL latfi(klon), lonfi(klon)
62      ! (latitude and longitude of a point of the scalar grid identified      ! (latitude and longitude of a point of the scalar grid identified
63      ! by a simple index, in °)      ! by a simple index, in degrees)
64    
65      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta
66      REAL vcov(iim + 1, jjm, llm)      REAL vcov(iim + 1, jjm, llm)
# Line 69  contains Line 71  contains
71      ! and pressure level "pls(i, j, l)".)      ! and pressure level "pls(i, j, l)".)
72    
73      real qsat(iim + 1, jjm + 1, llm) ! mass fraction of saturating water vapor      real qsat(iim + 1, jjm + 1, llm) ! mass fraction of saturating water vapor
74      REAL tsol(klon), qsol(klon), sn(klon)      REAL sn(klon)
75      REAL tsolsrf(klon, nbsrf), qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)      REAL qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)
76      REAL albe(klon, nbsrf), evap(klon, nbsrf)      REAL albe(klon, nbsrf), evap(klon, nbsrf)
77      REAL alblw(klon, nbsrf)      REAL alblw(klon, nbsrf)
78      REAL tsoil(klon, nsoilmx, nbsrf)      REAL tsoil(klon, nsoilmx, nbsrf)
79      REAL radsol(klon), rain_fall(klon), snow_fall(klon)      REAL radsol(klon), rain_fall(klon), snow_fall(klon)
80      REAL solsw(klon), sollw(klon), fder(klon)      REAL solsw(klon), sollw(klon), fder(klon)
81      !IM "slab" ocean      !IM "slab" ocean
     REAL tslab(klon)  
82      real seaice(klon) ! kg m-2      real seaice(klon) ! kg m-2
83      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)
84      REAL rugmer(klon)      REAL rugmer(klon)
     REAL phis(iim + 1, jjm + 1) ! surface geopotential, in m2 s-2  
85      real, dimension(iim + 1, jjm + 1):: zmea_2d, zstd_2d, zsig_2d, zgam_2d      real, dimension(iim + 1, jjm + 1):: zmea_2d, zstd_2d, zsig_2d, zgam_2d
86      real, dimension(iim + 1, jjm + 1):: zthe_2d, zpic_2d, zval_2d      real, dimension(iim + 1, jjm + 1):: zthe_2d, zpic_2d, zval_2d
87      real, dimension(iim + 1, jjm + 1):: tsol_2d, qsol_2d, ps      real, dimension(iim + 1, jjm + 1):: tsol_2d, qsol_2d, ps
# Line 93  contains Line 93  contains
93      REAL run_off_lic_0(klon)      REAL run_off_lic_0(klon)
94      real clwcon(klon, llm), rnebcon(klon, llm), ratqs(klon, llm)      real clwcon(klon, llm), rnebcon(klon, llm), ratqs(klon, llm)
95    
96      ! Déclarations pour lecture glace de mer :      ! D\'eclarations pour lecture glace de mer :
97      INTEGER iml_lic, jml_lic      INTEGER iml_lic, jml_lic
98      INTEGER ncid, varid      INTEGER ncid, varid
99      REAL, pointer:: dlon_lic(:), dlat_lic(:)      REAL, pointer:: dlon_lic(:), dlat_lic(:)
# Line 108  contains Line 108  contains
108      REAL masse(iim + 1, jjm + 1, llm)      REAL masse(iim + 1, jjm + 1, llm)
109      REAL phi(iim + 1, jjm + 1, llm)      REAL phi(iim + 1, jjm + 1, llm)
110      REAL pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)      REAL pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)
111      REAL w(ip1jmp1, llm)      REAL w(iim + 1, jjm + 1, llm)
     REAL phystep  
112    
113      real sig1(klon, llm) ! section adiabatic updraft      real sig1(klon, llm) ! section adiabatic updraft
114      real w01(klon, llm) ! vertical velocity within adiabatic updraft      real w01(klon, llm) ! vertical velocity within adiabatic updraft
115    
116        real pls(iim + 1, jjm + 1, llm)
117        ! (pressure at mid-layer of LMDZ grid, in Pa)
118        ! "pls(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",
119        ! for layer "l")
120    
121        REAL p3d(iim + 1, jjm + 1, llm+1) ! pressure at layer interfaces, in Pa
122        ! ("p3d(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",
123        ! for interface "l")
124    
125      !---------------------------------      !---------------------------------
126    
127      print *, "Call sequence information: etat0"      print *, "Call sequence information: etat0"
128    
129      dtvr = daysec / real(day_step)      CALL iniconst
     print *, 'dtvr = ', dtvr  
130    
131      ! Construct a grid:      ! Construct a grid:
132    
133      pa = 5e4      pa = 5e4
134      CALL iniconst      CALL disvert
135        call test_disvert
136      CALL inigeom      CALL inigeom
137      CALL inifilr      CALL inifilr
138    
# Line 150  contains Line 158  contains
158      ! Compute pressure on intermediate levels:      ! Compute pressure on intermediate levels:
159      forall(l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps      forall(l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps
160      CALL exner_hyb(ps, p3d, pks, pk)      CALL exner_hyb(ps, p3d, pks, pk)
161      IF (MINVAL(pk) == MAXVAL(pk)) then      call assert(MINVAL(pk) /= MAXVAL(pk), '"pk" should not be constant')
        print *, '"pk" should not be constant'  
        stop 1  
     end IF  
162    
163      pls = preff * (pk / cpp)**(1. / kappa)      pls = preff * (pk / cpp)**(1. / kappa)
164      PRINT *, "minval(pls) = ", minval(pls)      PRINT *, "minval(pls) = ", minval(pls)
# Line 179  contains Line 184  contains
184              / apols              / apols
185      ENDDO      ENDDO
186    
187      ! Calcul de l'humidité à saturation :      ! Calcul de l'humidit\'e \`a saturation :
188      qsat = q_sat(t3d, pls)      qsat = q_sat(t3d, pls)
189      PRINT *, "minval(qsat) = ", minval(qsat)      PRINT *, "minval(qsat) = ", minval(qsat)
190      print *, "maxval(qsat) = ", maxval(qsat)      print *, "maxval(qsat) = ", maxval(qsat)
# Line 200  contains Line 205  contains
205      if (nqmx >= 5) then      if (nqmx >= 5) then
206         ! Ozone:         ! Ozone:
207         call regr_lat_time_coefoz         call regr_lat_time_coefoz
208         call regr_pr_o3(q(:, :, :, 5))         call regr_pr_o3(p3d, q(:, :, :, 5))
209         ! Convert from mole fraction to mass fraction:         ! Convert from mole fraction to mass fraction:
210         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.
211      end if      end if
212    
     tsol = pack(tsol_2d, dyn_phy)  
     qsol = pack(qsol_2d, dyn_phy)  
213      sn = 0. ! snow      sn = 0. ! snow
214      radsol = 0.      radsol = 0.
     tslab = 0. ! IM "slab" ocean  
215      seaice = 0.      seaice = 0.
216      rugmer = 0.001      rugmer = 0.001
217      zmea = pack(zmea_2d, dyn_phy)      zmea = pack(zmea_2d, dyn_phy)
# Line 240  contains Line 242  contains
242    
243      call nf95_close(ncid)      call nf95_close(ncid)
244    
245      ! Interpolation sur la grille T du modèle :      ! Interpolation sur la grille T du mod\`ele :
246      PRINT *, 'Dimensions de "landiceref.nc"'      PRINT *, 'Dimensions de "landiceref.nc"'
247      print *, "iml_lic = ", iml_lic      print *, "iml_lic = ", iml_lic
248      print *, "jml_lic = ", jml_lic      print *, "jml_lic = ", jml_lic
249    
250      ! Si les coordonnées sont en degrés, on les transforme :      ! Si les coordonn\'ees sont en degr\'es, on les transforme :
251      IF (MAXVAL(dlon_lic) > pi) THEN      IF (MAXVAL(dlon_lic) > pi) THEN
252         dlon_lic = dlon_lic * pi / 180.         dlon_lic = dlon_lic * pi / 180.
253      ENDIF      ENDIF
# Line 262  contains Line 264  contains
264      ! Passage sur la grille physique      ! Passage sur la grille physique
265      pctsrf = 0.      pctsrf = 0.
266      pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy)      pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy)
267      ! Adéquation avec le maque terre/mer      ! Ad\'equation avec le maque terre/mer
268      WHERE (pctsrf(:, is_lic) < EPSFRA) pctsrf(:, is_lic) = 0.      WHERE (pctsrf(:, is_lic) < EPSFRA) pctsrf(:, is_lic) = 0.
269      WHERE (zmasq < EPSFRA) pctsrf(:, is_lic) = 0.      WHERE (zmasq < EPSFRA) pctsrf(:, is_lic) = 0.
270      pctsrf(:, is_ter) = zmasq      pctsrf(:, is_ter) = zmasq
# Line 279  contains Line 281  contains
281         end where         end where
282      end where      end where
283    
284      ! Sous-surface océan et glace de mer (pour démarrer on met glace      ! Sous-surface oc\'ean et glace de mer (pour d\'emarrer on met glace
285      ! de mer à 0) :      ! de mer \`a 0) :
286      pctsrf(:, is_oce) = 1. - zmasq      pctsrf(:, is_oce) = 1. - zmasq
287      WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0.      WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0.
288    
289      ! Vérification que somme des sous-surfaces vaut 1 :      ! V\'erification que somme des sous-surfaces vaut 1 :
290      ji = count(abs(sum(pctsrf, dim = 2) - 1.) > EPSFRA)      ji = count(abs(sum(pctsrf, dim = 2) - 1.) > EPSFRA)
291      IF (ji /= 0) then      IF (ji /= 0) then
292         PRINT *, 'Problème répartition sous maille pour ', ji, 'points'         PRINT *, 'Bad surface percentages for ', ji, 'points'
293      end IF      end IF
294    
295      ! Calcul intermédiaire :      ! Calcul interm\'ediaire :
296      CALL massdair(p3d, masse)      CALL massdair(p3d, masse)
297    
     print *, 'ALPHAX = ', alphax  
   
298      forall (l = 1:llm)      forall (l = 1:llm)
299         masse(:, 1, l) = SUM(aire_2d(:iim, 1) * masse(:iim, 1, l)) / apoln         masse(:, 1, l) = SUM(aire_2d(:iim, 1) * masse(:iim, 1, l)) / apoln
300         masse(:, jjm + 1, l) = &         masse(:, jjm + 1, l) = &
# Line 313  contains Line 313  contains
313      CALL dynredem0("start.nc", dayref, phis)      CALL dynredem0("start.nc", dayref, phis)
314      CALL dynredem1("start.nc", vcov, ucov, teta, q, masse, ps, itau=0)      CALL dynredem1("start.nc", vcov, ucov, teta, q, masse, ps, itau=0)
315    
     ! Ecriture état initial physique:  
     print *, "iphysiq = ", iphysiq  
     phystep = dtvr * REAL(iphysiq)  
     print *, 'phystep = ', phystep  
   
316      ! Initialisations :      ! Initialisations :
     tsolsrf(:, is_ter) = tsol  
     tsolsrf(:, is_lic) = tsol  
     tsolsrf(:, is_oce) = tsol  
     tsolsrf(:, is_sic) = tsol  
317      snsrf(:, is_ter) = sn      snsrf(:, is_ter) = sn
318      snsrf(:, is_lic) = sn      snsrf(:, is_lic) = sn
319      snsrf(:, is_oce) = sn      snsrf(:, is_oce) = sn
# Line 333  contains Line 324  contains
324      albe(:, is_sic) = 0.6      albe(:, is_sic) = 0.6
325      alblw = albe      alblw = albe
326      evap = 0.      evap = 0.
327      qsolsrf(:, is_ter) = 150.      qsolsrf = 150.
328      qsolsrf(:, is_lic) = 150.      tsoil = spread(spread(pack(tsol_2d, dyn_phy), 2, nsoilmx), 3, nbsrf)
     qsolsrf(:, is_oce) = 150.  
     qsolsrf(:, is_sic) = 150.  
     tsoil = spread(spread(tsol, 2, nsoilmx), 3, nbsrf)  
329      rain_fall = 0.      rain_fall = 0.
330      snow_fall = 0.      snow_fall = 0.
331      solsw = 165.      solsw = 165.
# Line 345  contains Line 333  contains
333      t_ancien = 273.15      t_ancien = 273.15
334      q_ancien = 0.      q_ancien = 0.
335      agesno = 0.      agesno = 0.
     !IM "slab" ocean  
     tslab = tsolsrf(:, is_oce)  
336      seaice = 0.      seaice = 0.
337    
338      frugs(:, is_oce) = rugmer      frugs(:, is_oce) = rugmer
# Line 361  contains Line 347  contains
347      sig1 = 0.      sig1 = 0.
348      w01 = 0.      w01 = 0.
349    
350      call phyredem("startphy.nc", latfi, lonfi, pctsrf, &      call phyredem("startphy.nc", latfi, lonfi, pctsrf, tsoil(:, 1, :), tsoil, &
351           tsolsrf, tsoil, tslab, seaice, qsolsrf, qsol, snsrf, albe, alblw, &           tsoil(:, 1, is_oce), seaice, qsolsrf, pack(qsol_2d, dyn_phy), snsrf, &
352           evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, frugs, &           albe, alblw, evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, &
353           agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &           frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, &
354           t_ancien, q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)           q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)
355      CALL histclo      CALL histclo
356    
357    END SUBROUTINE etat0    END SUBROUTINE etat0

Legend:
Removed from v.78  
changed lines
  Added in v.113

  ViewVC Help
Powered by ViewVC 1.1.21