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

Diff of /trunk/dyn3d/etat0.f90

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

trunk/dyn3d/etat0.f90 revision 79 by guez, Fri Feb 28 17:52:47 2014 UTC trunk/dyn3d/etat0.f revision 107 by guez, Thu Sep 11 15:09:15 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: cpp, kappa, iniconst      use comconst, only: cpp, kappa, iniconst
# 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
# Line 53  contains Line 52  contains
52      use start_init_phys_m, only: start_init_phys      use start_init_phys_m, only: start_init_phys
53      use start_inter_3d_m, only: start_inter_3d      use start_inter_3d_m, only: start_inter_3d
54      use temps, only: itau_phy, annee_ref, day_ref      use temps, only: itau_phy, annee_ref, day_ref
55        use test_disvert_m, only: test_disvert
56    
57      ! Variables local to the procedure:      REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)
58        ! surface geopotential, in m2 s-2
59    
60        ! Local:
61    
62      REAL latfi(klon), lonfi(klon)      REAL latfi(klon), lonfi(klon)
63      ! (latitude and longitude of a point of the scalar grid identified      ! (latitude and longitude of a point of the scalar grid identified
64      ! by a simple index, in °)      ! by a simple index, in degrees)
65    
66      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta
67      REAL vcov(iim + 1, jjm, llm)      REAL vcov(iim + 1, jjm, llm)
# Line 69  contains Line 72  contains
72      ! and pressure level "pls(i, j, l)".)      ! and pressure level "pls(i, j, l)".)
73    
74      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
75      REAL tsol(klon), qsol(klon), sn(klon)      REAL sn(klon)
76      REAL tsolsrf(klon, nbsrf), qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)      REAL qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)
77      REAL albe(klon, nbsrf), evap(klon, nbsrf)      REAL albe(klon, nbsrf), evap(klon, nbsrf)
78      REAL alblw(klon, nbsrf)      REAL alblw(klon, nbsrf)
79      REAL tsoil(klon, nsoilmx, nbsrf)      REAL tsoil(klon, nsoilmx, nbsrf)
80      REAL radsol(klon), rain_fall(klon), snow_fall(klon)      REAL radsol(klon), rain_fall(klon), snow_fall(klon)
81      REAL solsw(klon), sollw(klon), fder(klon)      REAL solsw(klon), sollw(klon), fder(klon)
82      !IM "slab" ocean      !IM "slab" ocean
     REAL tslab(klon)  
83      real seaice(klon) ! kg m-2      real seaice(klon) ! kg m-2
84      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)
85      REAL rugmer(klon)      REAL rugmer(klon)
     REAL phis(iim + 1, jjm + 1) ! surface geopotential, in m2 s-2  
86      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
87      real, dimension(iim + 1, jjm + 1):: zthe_2d, zpic_2d, zval_2d      real, dimension(iim + 1, jjm + 1):: zthe_2d, zpic_2d, zval_2d
88      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 94  contains
94      REAL run_off_lic_0(klon)      REAL run_off_lic_0(klon)
95      real clwcon(klon, llm), rnebcon(klon, llm), ratqs(klon, llm)      real clwcon(klon, llm), rnebcon(klon, llm), ratqs(klon, llm)
96    
97      ! Déclarations pour lecture glace de mer :      ! D\'eclarations pour lecture glace de mer :
98      INTEGER iml_lic, jml_lic      INTEGER iml_lic, jml_lic
99      INTEGER ncid, varid      INTEGER ncid, varid
100      REAL, pointer:: dlon_lic(:), dlat_lic(:)      REAL, pointer:: dlon_lic(:), dlat_lic(:)
# Line 108  contains Line 109  contains
109      REAL masse(iim + 1, jjm + 1, llm)      REAL masse(iim + 1, jjm + 1, llm)
110      REAL phi(iim + 1, jjm + 1, llm)      REAL phi(iim + 1, jjm + 1, llm)
111      REAL pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)      REAL pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)
112      REAL w(ip1jmp1, llm)      REAL w(iim + 1, jjm + 1, llm)
113    
114      real sig1(klon, llm) ! section adiabatic updraft      real sig1(klon, llm) ! section adiabatic updraft
115      real w01(klon, llm) ! vertical velocity within adiabatic updraft      real w01(klon, llm) ! vertical velocity within adiabatic updraft
116    
117        real pls(iim + 1, jjm + 1, llm)
118        ! (pressure at mid-layer of LMDZ grid, in Pa)
119        ! "pls(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",
120        ! for layer "l")
121    
122        REAL p3d(iim + 1, jjm + 1, llm+1) ! pressure at layer interfaces, in Pa
123        ! ("p3d(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",
124        ! for interface "l")
125    
126      !---------------------------------      !---------------------------------
127    
128      print *, "Call sequence information: etat0"      print *, "Call sequence information: etat0"
# Line 123  contains Line 133  contains
133    
134      pa = 5e4      pa = 5e4
135      CALL disvert      CALL disvert
136        call test_disvert
137      CALL inigeom      CALL inigeom
138      CALL inifilr      CALL inifilr
139    
# Line 148  contains Line 159  contains
159      ! Compute pressure on intermediate levels:      ! Compute pressure on intermediate levels:
160      forall(l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps      forall(l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps
161      CALL exner_hyb(ps, p3d, pks, pk)      CALL exner_hyb(ps, p3d, pks, pk)
162      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  
163    
164      pls = preff * (pk / cpp)**(1. / kappa)      pls = preff * (pk / cpp)**(1. / kappa)
165      PRINT *, "minval(pls) = ", minval(pls)      PRINT *, "minval(pls) = ", minval(pls)
# Line 177  contains Line 185  contains
185              / apols              / apols
186      ENDDO      ENDDO
187    
188      ! Calcul de l'humidité à saturation :      ! Calcul de l'humidit\'e \`a saturation :
189      qsat = q_sat(t3d, pls)      qsat = q_sat(t3d, pls)
190      PRINT *, "minval(qsat) = ", minval(qsat)      PRINT *, "minval(qsat) = ", minval(qsat)
191      print *, "maxval(qsat) = ", maxval(qsat)      print *, "maxval(qsat) = ", maxval(qsat)
# Line 198  contains Line 206  contains
206      if (nqmx >= 5) then      if (nqmx >= 5) then
207         ! Ozone:         ! Ozone:
208         call regr_lat_time_coefoz         call regr_lat_time_coefoz
209         call regr_pr_o3(q(:, :, :, 5))         call regr_pr_o3(p3d, q(:, :, :, 5))
210         ! Convert from mole fraction to mass fraction:         ! Convert from mole fraction to mass fraction:
211         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.
212      end if      end if
213    
     tsol = pack(tsol_2d, dyn_phy)  
     qsol = pack(qsol_2d, dyn_phy)  
214      sn = 0. ! snow      sn = 0. ! snow
215      radsol = 0.      radsol = 0.
     tslab = 0. ! IM "slab" ocean  
216      seaice = 0.      seaice = 0.
217      rugmer = 0.001      rugmer = 0.001
218      zmea = pack(zmea_2d, dyn_phy)      zmea = pack(zmea_2d, dyn_phy)
# Line 238  contains Line 243  contains
243    
244      call nf95_close(ncid)      call nf95_close(ncid)
245    
246      ! Interpolation sur la grille T du modèle :      ! Interpolation sur la grille T du mod\`ele :
247      PRINT *, 'Dimensions de "landiceref.nc"'      PRINT *, 'Dimensions de "landiceref.nc"'
248      print *, "iml_lic = ", iml_lic      print *, "iml_lic = ", iml_lic
249      print *, "jml_lic = ", jml_lic      print *, "jml_lic = ", jml_lic
250    
251      ! Si les coordonnées sont en degrés, on les transforme :      ! Si les coordonn\'ees sont en degr\'es, on les transforme :
252      IF (MAXVAL(dlon_lic) > pi) THEN      IF (MAXVAL(dlon_lic) > pi) THEN
253         dlon_lic = dlon_lic * pi / 180.         dlon_lic = dlon_lic * pi / 180.
254      ENDIF      ENDIF
# Line 260  contains Line 265  contains
265      ! Passage sur la grille physique      ! Passage sur la grille physique
266      pctsrf = 0.      pctsrf = 0.
267      pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy)      pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy)
268      ! Adéquation avec le maque terre/mer      ! Ad\'equation avec le maque terre/mer
269      WHERE (pctsrf(:, is_lic) < EPSFRA) pctsrf(:, is_lic) = 0.      WHERE (pctsrf(:, is_lic) < EPSFRA) pctsrf(:, is_lic) = 0.
270      WHERE (zmasq < EPSFRA) pctsrf(:, is_lic) = 0.      WHERE (zmasq < EPSFRA) pctsrf(:, is_lic) = 0.
271      pctsrf(:, is_ter) = zmasq      pctsrf(:, is_ter) = zmasq
# Line 277  contains Line 282  contains
282         end where         end where
283      end where      end where
284    
285      ! 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
286      ! de mer à 0) :      ! de mer \`a 0) :
287      pctsrf(:, is_oce) = 1. - zmasq      pctsrf(:, is_oce) = 1. - zmasq
288      WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0.      WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0.
289    
290      ! Vérification que somme des sous-surfaces vaut 1 :      ! V\'erification que somme des sous-surfaces vaut 1 :
291      ji = count(abs(sum(pctsrf, dim = 2) - 1.) > EPSFRA)      ji = count(abs(sum(pctsrf, dim = 2) - 1.) > EPSFRA)
292      IF (ji /= 0) then      IF (ji /= 0) then
293         PRINT *, 'Problème répartition sous maille pour ', ji, 'points'         PRINT *, 'Bad surface percentages for ', ji, 'points'
294      end IF      end IF
295    
296      ! Calcul intermédiaire :      ! Calcul interm\'ediaire :
297      CALL massdair(p3d, masse)      CALL massdair(p3d, masse)
298    
299      print *, 'ALPHAX = ', alphax      print *, 'ALPHAX = ', alphax
# Line 312  contains Line 317  contains
317      CALL dynredem1("start.nc", vcov, ucov, teta, q, masse, ps, itau=0)      CALL dynredem1("start.nc", vcov, ucov, teta, q, masse, ps, itau=0)
318    
319      ! Initialisations :      ! Initialisations :
     tsolsrf(:, is_ter) = tsol  
     tsolsrf(:, is_lic) = tsol  
     tsolsrf(:, is_oce) = tsol  
     tsolsrf(:, is_sic) = tsol  
320      snsrf(:, is_ter) = sn      snsrf(:, is_ter) = sn
321      snsrf(:, is_lic) = sn      snsrf(:, is_lic) = sn
322      snsrf(:, is_oce) = sn      snsrf(:, is_oce) = sn
# Line 326  contains Line 327  contains
327      albe(:, is_sic) = 0.6      albe(:, is_sic) = 0.6
328      alblw = albe      alblw = albe
329      evap = 0.      evap = 0.
330      qsolsrf(:, is_ter) = 150.      qsolsrf = 150.
331      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)  
332      rain_fall = 0.      rain_fall = 0.
333      snow_fall = 0.      snow_fall = 0.
334      solsw = 165.      solsw = 165.
# Line 338  contains Line 336  contains
336      t_ancien = 273.15      t_ancien = 273.15
337      q_ancien = 0.      q_ancien = 0.
338      agesno = 0.      agesno = 0.
     !IM "slab" ocean  
     tslab = tsolsrf(:, is_oce)  
339      seaice = 0.      seaice = 0.
340    
341      frugs(:, is_oce) = rugmer      frugs(:, is_oce) = rugmer
# Line 354  contains Line 350  contains
350      sig1 = 0.      sig1 = 0.
351      w01 = 0.      w01 = 0.
352    
353      call phyredem("startphy.nc", latfi, lonfi, pctsrf, &      call phyredem("startphy.nc", latfi, lonfi, pctsrf, tsoil(:, 1, :), tsoil, &
354           tsolsrf, tsoil, tslab, seaice, qsolsrf, qsol, snsrf, albe, alblw, &           tsoil(:, 1, is_oce), seaice, qsolsrf, pack(qsol_2d, dyn_phy), snsrf, &
355           evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, frugs, &           albe, alblw, evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, &
356           agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &           frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, &
357           t_ancien, q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)           q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)
358      CALL histclo      CALL histclo
359    
360    END SUBROUTINE etat0    END SUBROUTINE etat0

Legend:
Removed from v.79  
changed lines
  Added in v.107

  ViewVC Help
Powered by ViewVC 1.1.21