/[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.f revision 82 by guez, Wed Mar 5 14:57:53 2014 UTC trunk/Sources/dyn3d/etat0.f revision 138 by guez, Fri May 22 23:13:19 2015 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
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
     use conf_gcm_m, only: dayref, anneeref  
24      use dimens_m, only: iim, jjm, llm, nqmx      use dimens_m, only: iim, jjm, llm, nqmx
25      use dimphy, only: zmasq      use dimphy, only: zmasq
26      use dimsoil, only: nsoilmx      use dimsoil, only: nsoilmx
27      use disvert_m, only: ap, bp, preff, pa, disvert      use disvert_m, only: ap, bp, preff, pa, disvert
28        use dynetat0_m, only: day_ref, annee_ref
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
32      use geopot_m, only: geopot      use geopot_m, only: geopot
33      use grid_atob, only: grille_m      use grid_atob, only: grille_m
34      use grid_change, only: init_dyn_phy, dyn_phy      use grid_change, only: init_dyn_phy, dyn_phy
     use histclo_m, only: histclo  
35      use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra      use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra
36      use iniadvtrac_m, only: iniadvtrac      use iniadvtrac_m, only: iniadvtrac
37      use inifilr_m, only: inifilr      use inifilr_m, only: inifilr
# Line 40  contains Line 39  contains
39      use netcdf, only: nf90_nowrite      use netcdf, only: nf90_nowrite
40      use netcdf95, only: nf95_close, nf95_get_var, nf95_gw_var, &      use netcdf95, only: nf95_close, nf95_get_var, nf95_gw_var, &
41           nf95_inq_varid, nf95_open           nf95_inq_varid, nf95_open
42      use nr_util, only: pi      use nr_util, only: pi, assert
43      use paramet_m, only: ip1jm, ip1jmp1      use paramet_m, only: ip1jm, ip1jmp1
44        use phyetat0_m, only: rlat, rlon
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
54        use test_disvert_m, only: test_disvert
55        use unit_nml_m, only: unit_nml
56    
57      ! Variables local to the procedure:      REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)
58        ! surface geopotential, in m2 s-2
59    
60      REAL latfi(klon), lonfi(klon)      ! Local:
     ! (latitude and longitude of a point of the scalar grid identified  
     ! by a simple index, in °)  
61    
62      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta
63      REAL vcov(iim + 1, jjm, llm)      REAL vcov(iim + 1, jjm, llm)
# Line 69  contains Line 68  contains
68      ! and pressure level "pls(i, j, l)".)      ! and pressure level "pls(i, j, l)".)
69    
70      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
71      REAL tsol(klon), qsol(klon), sn(klon)      REAL sn(klon)
72      REAL tsolsrf(klon, nbsrf), qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)      REAL qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)
73      REAL albe(klon, nbsrf), evap(klon, nbsrf)      REAL albe(klon, nbsrf), evap(klon, nbsrf)
74      REAL alblw(klon, nbsrf)      REAL alblw(klon, nbsrf)
75      REAL tsoil(klon, nsoilmx, nbsrf)      REAL tsoil(klon, nsoilmx, nbsrf)
76      REAL radsol(klon), rain_fall(klon), snow_fall(klon)      REAL radsol(klon), rain_fall(klon), snow_fall(klon)
77      REAL solsw(klon), sollw(klon), fder(klon)      REAL solsw(klon), sollw(klon), fder(klon)
78      !IM "slab" ocean      !IM "slab" ocean
     REAL tslab(klon)  
79      real seaice(klon) ! kg m-2      real seaice(klon) ! kg m-2
80      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)
81      REAL rugmer(klon)      REAL rugmer(klon)
     REAL phis(iim + 1, jjm + 1) ! surface geopotential, in m2 s-2  
82      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
83      real, dimension(iim + 1, jjm + 1):: zthe_2d, zpic_2d, zval_2d      real, dimension(iim + 1, jjm + 1):: zthe_2d, zpic_2d, zval_2d
84      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 90  contains
90      REAL run_off_lic_0(klon)      REAL run_off_lic_0(klon)
91      real clwcon(klon, llm), rnebcon(klon, llm), ratqs(klon, llm)      real clwcon(klon, llm), rnebcon(klon, llm), ratqs(klon, llm)
92    
93      ! Déclarations pour lecture glace de mer :      ! D\'eclarations pour lecture glace de mer :
94      INTEGER iml_lic, jml_lic      INTEGER iml_lic, jml_lic
95      INTEGER ncid, varid      INTEGER ncid, varid
96      REAL, pointer:: dlon_lic(:), dlat_lic(:)      REAL, pointer:: dlon_lic(:), dlat_lic(:)
# Line 108  contains Line 105  contains
105      REAL masse(iim + 1, jjm + 1, llm)      REAL masse(iim + 1, jjm + 1, llm)
106      REAL phi(iim + 1, jjm + 1, llm)      REAL phi(iim + 1, jjm + 1, llm)
107      REAL pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)      REAL pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)
108      REAL w(ip1jmp1, llm)      REAL w(iim + 1, jjm + 1, llm)
109    
110      real sig1(klon, llm) ! section adiabatic updraft      real sig1(klon, llm) ! section adiabatic updraft
111      real w01(klon, llm) ! vertical velocity within adiabatic updraft      real w01(klon, llm) ! vertical velocity within adiabatic updraft
112    
113        real pls(iim + 1, jjm + 1, llm)
114        ! (pressure at mid-layer of LMDZ grid, in Pa)
115        ! "pls(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",
116        ! for layer "l")
117    
118        REAL p3d(iim + 1, jjm + 1, llm+1) ! pressure at layer interfaces, in Pa
119        ! ("p3d(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",
120        ! for interface "l")
121    
122        namelist /etat0_nml/ day_ref, annee_ref
123    
124      !---------------------------------      !---------------------------------
125    
126      print *, "Call sequence information: etat0"      print *, "Call sequence information: etat0"
127    
128        print *, "Enter namelist 'etat0_nml'."
129        read(unit=*, nml=etat0_nml)
130        write(unit_nml, nml=etat0_nml)
131    
132      CALL iniconst      CALL iniconst
133    
134      ! Construct a grid:      ! Construct a grid:
135    
136      pa = 5e4      pa = 5e4
137      CALL disvert      CALL disvert
138        call test_disvert
139      CALL inigeom      CALL inigeom
140      CALL inifilr      CALL inifilr
141    
142      latfi(1) = 90.      rlat(1) = 90.
143      latfi(2:klon-1) = pack(spread(rlatu(2:jjm), 1, iim), .true.) * 180. / pi      rlat(2:klon-1) = pack(spread(rlatu(2:jjm), 1, iim), .true.) * 180. / pi
144      ! (with conversion to degrees)      ! (with conversion to degrees)
145      latfi(klon) = - 90.      rlat(klon) = - 90.
146    
147      lonfi(1) = 0.      rlon(1) = 0.
148      lonfi(2:klon-1) = pack(spread(rlonv(:iim), 2, jjm - 1), .true.) * 180. / pi      rlon(2:klon-1) = pack(spread(rlonv(:iim), 2, jjm - 1), .true.) * 180. / pi
149      ! (with conversion to degrees)      ! (with conversion to degrees)
150      lonfi(klon) = 0.      rlon(klon) = 0.
151    
152      call start_init_orog(phis, zmea_2d, zstd_2d, zsig_2d, zgam_2d, zthe_2d, &      call start_init_orog(phis, zmea_2d, zstd_2d, zsig_2d, zgam_2d, zthe_2d, &
153           zpic_2d, zval_2d) ! also compute "mask"           zpic_2d, zval_2d) ! also compute "mask"
# Line 148  contains Line 161  contains
161      ! Compute pressure on intermediate levels:      ! Compute pressure on intermediate levels:
162      forall(l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps      forall(l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps
163      CALL exner_hyb(ps, p3d, pks, pk)      CALL exner_hyb(ps, p3d, pks, pk)
164      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  
165    
166      pls = preff * (pk / cpp)**(1. / kappa)      pls = preff * (pk / cpp)**(1. / kappa)
167      PRINT *, "minval(pls) = ", minval(pls)      PRINT *, "minval(pls) = ", minval(pls)
# Line 177  contains Line 187  contains
187              / apols              / apols
188      ENDDO      ENDDO
189    
190      ! Calcul de l'humidité à saturation :      ! Calcul de l'humidit\'e \`a saturation :
191      qsat = q_sat(t3d, pls)      qsat = q_sat(t3d, pls)
192      PRINT *, "minval(qsat) = ", minval(qsat)      PRINT *, "minval(qsat) = ", minval(qsat)
193      print *, "maxval(qsat) = ", maxval(qsat)      print *, "maxval(qsat) = ", maxval(qsat)
# Line 198  contains Line 208  contains
208      if (nqmx >= 5) then      if (nqmx >= 5) then
209         ! Ozone:         ! Ozone:
210         call regr_lat_time_coefoz         call regr_lat_time_coefoz
211         call regr_pr_o3(q(:, :, :, 5))         call regr_pr_o3(p3d, q(:, :, :, 5))
212         ! Convert from mole fraction to mass fraction:         ! Convert from mole fraction to mass fraction:
213         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.
214      end if      end if
215    
     tsol = pack(tsol_2d, dyn_phy)  
     qsol = pack(qsol_2d, dyn_phy)  
216      sn = 0. ! snow      sn = 0. ! snow
217      radsol = 0.      radsol = 0.
     tslab = 0. ! IM "slab" ocean  
218      seaice = 0.      seaice = 0.
219      rugmer = 0.001      rugmer = 0.001
220      zmea = pack(zmea_2d, dyn_phy)      zmea = pack(zmea_2d, dyn_phy)
# Line 238  contains Line 245  contains
245    
246      call nf95_close(ncid)      call nf95_close(ncid)
247    
248      ! Interpolation sur la grille T du modèle :      ! Interpolation sur la grille T du mod\`ele :
249      PRINT *, 'Dimensions de "landiceref.nc"'      PRINT *, 'Dimensions de "landiceref.nc"'
250      print *, "iml_lic = ", iml_lic      print *, "iml_lic = ", iml_lic
251      print *, "jml_lic = ", jml_lic      print *, "jml_lic = ", jml_lic
252    
253      ! Si les coordonnées sont en degrés, on les transforme :      ! Si les coordonn\'ees sont en degr\'es, on les transforme :
254      IF (MAXVAL(dlon_lic) > pi) THEN      IF (MAXVAL(dlon_lic) > pi) THEN
255         dlon_lic = dlon_lic * pi / 180.         dlon_lic = dlon_lic * pi / 180.
256      ENDIF      ENDIF
# Line 260  contains Line 267  contains
267      ! Passage sur la grille physique      ! Passage sur la grille physique
268      pctsrf = 0.      pctsrf = 0.
269      pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy)      pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy)
270      ! Adéquation avec le maque terre/mer      ! Ad\'equation avec le maque terre/mer
271      WHERE (pctsrf(:, is_lic) < EPSFRA) pctsrf(:, is_lic) = 0.      WHERE (pctsrf(:, is_lic) < EPSFRA) pctsrf(:, is_lic) = 0.
272      WHERE (zmasq < EPSFRA) pctsrf(:, is_lic) = 0.      WHERE (zmasq < EPSFRA) pctsrf(:, is_lic) = 0.
273      pctsrf(:, is_ter) = zmasq      pctsrf(:, is_ter) = zmasq
# Line 277  contains Line 284  contains
284         end where         end where
285      end where      end where
286    
287      ! 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
288      ! de mer à 0) :      ! de mer \`a 0) :
289      pctsrf(:, is_oce) = 1. - zmasq      pctsrf(:, is_oce) = 1. - zmasq
290      WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0.      WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0.
291    
292      ! Vérification que somme des sous-surfaces vaut 1 :      ! V\'erification que somme des sous-surfaces vaut 1 :
293      ji = count(abs(sum(pctsrf, dim = 2) - 1.) > EPSFRA)      ji = count(abs(sum(pctsrf, dim = 2) - 1.) > EPSFRA)
294      IF (ji /= 0) then      IF (ji /= 0) then
295         PRINT *, 'Problème répartition sous maille pour ', ji, 'points'         PRINT *, 'Bad surface percentages for ', ji, 'points'
296      end IF      end IF
297    
298      ! Calcul intermédiaire :      ! Calcul interm\'ediaire :
299      CALL massdair(p3d, masse)      CALL massdair(p3d, masse)
300    
     print *, 'ALPHAX = ', alphax  
   
301      forall (l = 1:llm)      forall (l = 1:llm)
302         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
303         masse(:, jjm + 1, l) = &         masse(:, jjm + 1, l) = &
# Line 302  contains Line 307  contains
307      ! Initialisation pour traceurs:      ! Initialisation pour traceurs:
308      call iniadvtrac      call iniadvtrac
309      itau_phy = 0      itau_phy = 0
     day_ref = dayref  
     annee_ref = anneeref  
310    
311      CALL geopot(teta, pk , pks, phis, phi)      CALL geopot(teta, pk , pks, phis, phi)
312      CALL caldyn0(ucov, vcov, teta, ps, masse, pk, phis, phi, w, pbaru, &      CALL caldyn0(ucov, vcov, teta, ps, masse, pk, phis, phi, w, pbaru, &
313           pbarv)           pbarv)
314      CALL dynredem0("start.nc", dayref, phis)      CALL dynredem0("start.nc", day_ref, phis)
315      CALL dynredem1("start.nc", vcov, ucov, teta, q, masse, ps, itau=0)      CALL dynredem1("start.nc", vcov, ucov, teta, q, masse, ps, itau=0)
316    
317      ! Initialisations :      ! Initialisations :
     tsolsrf(:, is_ter) = tsol  
     tsolsrf(:, is_lic) = tsol  
     tsolsrf(:, is_oce) = tsol  
     tsolsrf(:, is_sic) = tsol  
318      snsrf(:, is_ter) = sn      snsrf(:, is_ter) = sn
319      snsrf(:, is_lic) = sn      snsrf(:, is_lic) = sn
320      snsrf(:, is_oce) = sn      snsrf(:, is_oce) = sn
# Line 326  contains Line 325  contains
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 = 150.
329      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)  
330      rain_fall = 0.      rain_fall = 0.
331      snow_fall = 0.      snow_fall = 0.
332      solsw = 165.      solsw = 165.
# Line 338  contains Line 334  contains
334      t_ancien = 273.15      t_ancien = 273.15
335      q_ancien = 0.      q_ancien = 0.
336      agesno = 0.      agesno = 0.
     !IM "slab" ocean  
     tslab = tsolsrf(:, is_oce)  
337      seaice = 0.      seaice = 0.
338    
339      frugs(:, is_oce) = rugmer      frugs(:, is_oce) = rugmer
# Line 354  contains Line 348  contains
348      sig1 = 0.      sig1 = 0.
349      w01 = 0.      w01 = 0.
350    
351      call phyredem("startphy.nc", latfi, lonfi, pctsrf, &      call phyredem("startphy.nc", pctsrf, tsoil(:, 1, :), tsoil, &
352           tsolsrf, tsoil, tslab, seaice, qsolsrf, qsol, snsrf, albe, alblw, &           tsoil(:, 1, is_oce), seaice, qsolsrf, pack(qsol_2d, dyn_phy), snsrf, &
353           evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, frugs, &           albe, alblw, evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, &
354           agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &           frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, &
355           t_ancien, q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)           q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)
     CALL histclo  
356    
357    END SUBROUTINE etat0    END SUBROUTINE etat0
358    

Legend:
Removed from v.82  
changed lines
  Added in v.138

  ViewVC Help
Powered by ViewVC 1.1.21