/[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/Sources/dyn3d/etat0.f revision 178 by guez, Fri Mar 11 18:47:26 2016 UTC trunk/dyn3d/etat0.f90 revision 331 by guez, Wed Jul 31 17:10:31 2019 UTC
# Line 1  Line 1 
1  module etat0_mod  module etat0_m
   
   use indicesol, only: nbsrf  
   use dimphy, only: klon  
2    
3    IMPLICIT NONE    IMPLICIT NONE
4    
   REAL pctsrf(klon, nbsrf)  
   ! ("pctsrf(i, :)" is the composition of the surface at horizontal  
   ! position "i")  
   
   private nbsrf, klon  
   
5  contains  contains
6    
7    SUBROUTINE etat0(phis)    SUBROUTINE etat0(phis, pctsrf)
8    
9      ! 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
10    
11      use caldyn0_m, only: caldyn0      use caldyn0_m, only: caldyn0
12      use comconst, only: cpp, kappa, iniconst      use comconst, only: cpp, kappa, iniconst
13      use comgeom, only: aire_2d, apoln, apols, cu_2d, cv_2d, inigeom      use comgeom, only: aire_2d, apoln, apols, cu_2d, cv_2d, inigeom
14      use conf_gcm_m, only: nday, day_step, iphysiq      use conf_gcm_m, only: nday
15      use dimens_m, only: iim, jjm, llm, nqmx      use dimensions, only: iim, jjm, llm, nqmx
16      use dimphy, only: zmasq      use dimphy, only: klon
17      use dimsoil, only: nsoilmx      use dimsoil, only: nsoilmx
18      use disvert_m, only: ap, bp, preff, pa, disvert      use disvert_m, only: ap, bp, preff, disvert
19      use dynetat0_m, only: day_ref, annee_ref, xprimp025, xprimm025, rlatu1, &      use dynetat0_m, only: rlatu, rlatv, rlonu, rlonv, fyhyp, fxhyp
20           rlatu2, rlatu, rlatv, yprimu1, yprimu2, rlonu, rlonv, xprimu, xprimv      use dynetat0_chosen_m, only: day_ref
21      use dynredem0_m, only: dynredem0      use dynredem0_m, only: dynredem0
22      use dynredem1_m, only: dynredem1      use dynredem1_m, only: dynredem1
23      use exner_hyb_m, only: exner_hyb      use exner_hyb_m, only: exner_hyb
     use fxhyp_m, only: fxhyp  
     use fyhyp_m, only: fyhyp  
24      use geopot_m, only: geopot      use geopot_m, only: geopot
25      use grid_atob, only: grille_m      use grille_m_m, only: grille_m
26      use grid_change, only: init_dyn_phy, dyn_phy      use grid_change, only: init_dyn_phy, dyn_phy
27      use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra      use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra, nbsrf
28      use iniadvtrac_m, only: iniadvtrac      use infotrac_init_m, only: infotrac_init
29      use inifilr_m, only: inifilr      use inifilr_m, only: inifilr
30      use massdair_m, only: massdair      use massdair_m, only: massdair
31      use netcdf, only: nf90_nowrite      use netcdf, only: nf90_nowrite
32      use netcdf95, only: nf95_close, nf95_get_var, nf95_gw_var, nf95_put_var, &      use netcdf95, only: nf95_close, nf95_get_var, nf95_gw_var, nf95_put_var, &
33           nf95_inq_varid, nf95_open           nf95_inq_varid, nf95_open
34      use nr_util, only: pi, assert      use nr_util, only: pi, assert
35      use phyetat0_m, only: rlat, rlon      use phyetat0_m, only: masque, phyetat0_new
36      use phyredem0_m, only: phyredem0, ncid_restartphy      use phyredem0_m, only: phyredem0, ncid_restartphy
37      use phyredem_m, only: phyredem      use phyredem_m, only: phyredem
38      use q_sat_m, only: q_sat      use q_sat_m, only: q_sat
39      use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz      use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz
40      use regr_pr_o3_m, only: regr_pr_o3      use regr_pr_o3_m, only: regr_pr_o3
41      use startdyn, only: start_init_dyn      use startdyn, only: start_init_dyn
42      USE start_init_orog_m, only: start_init_orog, mask      USE start_init_orog_m, only: start_init_orog
43      use start_init_phys_m, only: start_init_phys      use start_init_phys_m, only: start_init_phys
44      use start_inter_3d_m, only: start_inter_3d      use start_inter_3d_m, only: start_inter_3d
45      use test_disvert_m, only: test_disvert      use test_disvert_m, only: test_disvert
     use unit_nml_m, only: unit_nml  
46    
47      REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)      REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)
48      ! surface geopotential, in m2 s-2      ! surface geopotential, in m2 s-2
49    
50        REAL, intent(out):: pctsrf(:, :) ! (klon, nbsrf)
51        ! "pctsrf(i, :)" is the composition of the surface at horizontal
52        ! position "i".
53    
54      ! Local:      ! Local:
55    
56      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta
# Line 70  contains Line 62  contains
62      ! and pressure level "pls(i, j, l)".)      ! and pressure level "pls(i, j, l)".)
63    
64      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
65      REAL qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)      REAL qsolsrf(klon, nbsrf), fsnow(klon, nbsrf)
66      REAL albe(klon, nbsrf), evap(klon, nbsrf)      REAL falbe(klon, nbsrf)
67      REAL tsoil(klon, nsoilmx, nbsrf)      REAL tsoil(klon, nsoilmx, nbsrf)
68      REAL null_array(klon)      REAL null_array(klon)
69      REAL solsw(klon), sollw(klon)      REAL solsw(klon), sollw(klon)
# Line 91  contains Line 83  contains
83      ! D\'eclarations pour lecture glace de mer :      ! D\'eclarations pour lecture glace de mer :
84      INTEGER iml_lic, jml_lic      INTEGER iml_lic, jml_lic
85      INTEGER ncid, varid      INTEGER ncid, varid
86      REAL, pointer:: dlon_lic(:), dlat_lic(:)      REAL, ALLOCATABLE:: dlon_lic(:), dlat_lic(:)
87      REAL, ALLOCATABLE:: fraclic(:, :) ! fraction land ice      REAL, ALLOCATABLE:: landice(:, :) ! fraction land ice
88      REAL flic_tmp(iim + 1, jjm + 1) ! fraction land ice temporary      REAL flic_tmp(iim + 1, jjm + 1) ! fraction land ice temporary
89    
90      INTEGER l, ji      INTEGER l, ji
# Line 113  contains Line 105  contains
105      ! ("p3d(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",      ! ("p3d(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",
106      ! for interface "l")      ! for interface "l")
107    
     namelist /etat0_nml/ day_ref, annee_ref  
   
108      !---------------------------------      !---------------------------------
109    
110      print *, "Call sequence information: etat0"      print *, "Call sequence information: etat0"
111    
     print *, "Enter namelist 'etat0_nml'."  
     read(unit=*, nml=etat0_nml)  
     write(unit_nml, nml=etat0_nml)  
   
112      CALL iniconst      CALL iniconst
113    
114      ! Construct a grid:      ! Construct a grid:
115    
     pa = 5e4  
116      CALL disvert      CALL disvert
117      call test_disvert      call test_disvert
118        CALL fyhyp
119      CALL fyhyp(rlatu, rlatv, rlatu2, yprimu2, rlatu1, yprimu1)      CALL fxhyp
     CALL fxhyp(xprimm025, rlonv, xprimv, rlonu, xprimu, xprimp025)  
   
     rlatu(1) = pi / 2.  
     rlatu(jjm + 1) = -rlatu(1)  
   
120      CALL inigeom      CALL inigeom
121      CALL inifilr      CALL inifilr
   
     rlat(1) = 90.  
     rlat(2:klon-1) = pack(spread(rlatu(2:jjm), 1, iim), .true.) * 180. / pi  
     ! (with conversion to degrees)  
     rlat(klon) = - 90.  
   
     rlon(1) = 0.  
     rlon(2:klon-1) = pack(spread(rlonv(:iim), 2, jjm - 1), .true.) * 180. / pi  
     ! (with conversion to degrees)  
     rlon(klon) = 0.  
   
122      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, &
123           zpic_2d, zval_2d) ! also compute "mask"           zpic_2d, zval_2d) ! also compute "mask"
124      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
125      zmasq = pack(mask, dyn_phy)      call phyetat0_new
     PRINT *, 'Masque construit'  
126    
127      call start_init_phys(tsol_2d, qsol_2d)      call start_init_phys(tsol_2d, qsol_2d)
128      CALL start_init_dyn(tsol_2d, phis, ps)      CALL start_init_dyn(tsol_2d, phis, ps)
# Line 239  contains Line 207  contains
207      jml_lic = size(dlat_lic)      jml_lic = size(dlat_lic)
208    
209      call nf95_inq_varid(ncid, 'landice', varid)      call nf95_inq_varid(ncid, 'landice', varid)
210      ALLOCATE(fraclic(iml_lic, jml_lic))      ALLOCATE(landice(iml_lic, jml_lic))
211      call nf95_get_var(ncid, varid, fraclic)      call nf95_get_var(ncid, varid, landice)
212    
213      call nf95_close(ncid)      call nf95_close(ncid)
214    
# Line 257  contains Line 225  contains
225         dlat_lic = dlat_lic * pi/ 180.         dlat_lic = dlat_lic * pi/ 180.
226      ENDIF      ENDIF
227    
228      flic_tmp(:iim, :) = grille_m(dlon_lic, dlat_lic, fraclic, rlonv(:iim), &      flic_tmp(:iim, :) = grille_m(dlon_lic, dlat_lic, landice, rlonv(:iim), &
229           rlatu)           rlatu)
230      flic_tmp(iim + 1, :) = flic_tmp(1, :)      flic_tmp(iim + 1, :) = flic_tmp(1, :)
231    
232      deallocate(dlon_lic, dlat_lic) ! pointers      ! Passage sur la grille physique :
   
     ! Passage sur la grille physique  
233      pctsrf = 0.      pctsrf = 0.
234      pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy)      pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy)
235      ! Ad\'equation avec le maque terre/mer      
236        ! Ad\'equation avec le maque terre/mer :
237      WHERE (pctsrf(:, is_lic) < EPSFRA) pctsrf(:, is_lic) = 0.      WHERE (pctsrf(:, is_lic) < EPSFRA) pctsrf(:, is_lic) = 0.
238      WHERE (zmasq < EPSFRA) pctsrf(:, is_lic) = 0.      WHERE (masque < EPSFRA) pctsrf(:, is_lic) = 0.
239      pctsrf(:, is_ter) = zmasq      where (masque <= EPSFRA) pctsrf(:, is_ter) = masque
240      where (zmasq > EPSFRA)      where (masque > EPSFRA)
241         where (pctsrf(:, is_lic) >= zmasq)         where (pctsrf(:, is_lic) >= masque)
242            pctsrf(:, is_lic) = zmasq            pctsrf(:, is_lic) = masque
243            pctsrf(:, is_ter) = 0.            pctsrf(:, is_ter) = 0.
244         elsewhere         elsewhere
245            pctsrf(:, is_ter) = zmasq - pctsrf(:, is_lic)            pctsrf(:, is_ter) = masque - pctsrf(:, is_lic)
246            where (pctsrf(:, is_ter) < EPSFRA)            where (pctsrf(:, is_ter) < EPSFRA)
247               pctsrf(:, is_ter) = 0.               pctsrf(:, is_ter) = 0.
248               pctsrf(:, is_lic) = zmasq               pctsrf(:, is_lic) = masque
249            end where            end where
250         end where         end where
251      end where      end where
252    
253      ! Sous-surface oc\'ean et glace de mer (pour d\'emarrer on met glace      ! Sous-surface oc\'ean et glace de mer (pour d\'emarrer on met glace
254      ! de mer \`a 0) :      ! de mer \`a 0) :
255      pctsrf(:, is_oce) = 1. - zmasq      pctsrf(:, is_oce) = 1. - masque
256      WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0.      WHERE (pctsrf(:, is_oce) < EPSFRA) pctsrf(:, is_oce) = 0.
257    
258      ! V\'erification que la somme des sous-surfaces vaut 1 :      ! V\'erification que la somme des sous-surfaces vaut 1 :
# Line 303  contains Line 270  contains
270              SUM(aire_2d(:iim, jjm + 1) * masse(:iim, jjm + 1, l)) / apols              SUM(aire_2d(:iim, jjm + 1) * masse(:iim, jjm + 1, l)) / apols
271      END forall      END forall
272    
273      call iniadvtrac      call infotrac_init
274      CALL geopot(teta, pk , pks, phis, phi)      CALL geopot(teta, pk , pks, phis, phi)
275      CALL caldyn0(ucov, vcov, teta, ps, pk, phis, phi)      CALL caldyn0(ucov, vcov, teta, ps, pk, phis, phi)
276      CALL dynredem0(day_ref, phis)      CALL dynredem0(day_ref, phis)
277      CALL dynredem1(vcov, ucov, teta, q, masse, ps, itau = 0)      CALL dynredem1(vcov, ucov, teta, q, masse, ps, itau = 0)
278    
279      ! Initialisations :      ! Initialisations :
280      snsrf = 0.      fsnow = 0.
281      albe(:, is_ter) = 0.08      falbe(:, is_ter) = 0.08
282      albe(:, is_lic) = 0.6      falbe(:, is_lic) = 0.6
283      albe(:, is_oce) = 0.5      falbe(:, is_oce) = 0.5
284      albe(:, is_sic) = 0.6      falbe(:, is_sic) = 0.6
     evap = 0.  
285      qsolsrf = 150.      qsolsrf = 150.
286      tsoil = spread(spread(pack(tsol_2d, dyn_phy), 2, nsoilmx), 3, nbsrf)      tsoil = spread(spread(pack(tsol_2d, dyn_phy), 2, nsoilmx), 3, nbsrf)
287      solsw = 165.      solsw = 165.
# Line 334  contains Line 300  contains
300      sig1 = 0.      sig1 = 0.
301      w01 = 0.      w01 = 0.
302    
303      nday = 0      nday = 0 ! side effect
304      call phyredem0(lmt_pas = day_step / iphysiq, itau_phy = 0)      call phyredem0
305    
306      call nf95_inq_varid(ncid_restartphy, "trs", varid)      call nf95_inq_varid(ncid_restartphy, "trs", varid)
307      call nf95_put_var(ncid_restartphy, varid, null_array)      call nf95_put_var(ncid_restartphy, varid, null_array)
308    
309      call phyredem(pctsrf, tsoil(:, 1, :), tsoil, qsolsrf, &      call phyredem(pctsrf, tsoil(:, 1, :), tsoil, qsolsrf, &
310           pack(qsol_2d, dyn_phy), snsrf, albe, evap, null_array, null_array, &           pack(qsol_2d, dyn_phy), fsnow, falbe, null_array, null_array, solsw, &
311           solsw, sollw, null_array, null_array, frugs, agesno, zmea, zstd, &           sollw, null_array, null_array, frugs, agesno, zmea, zstd, zsig, zgam, &
312           zsig, zgam, zthe, zpic, zval, t_ancien, q_ancien, rnebcon, ratqs, &           zthe, zpic, zval, t_ancien, q_ancien, rnebcon, ratqs, clwcon, &
313           clwcon, null_array, sig1, w01)           null_array, sig1, w01)
314    
315    END SUBROUTINE etat0    END SUBROUTINE etat0
316    
317  end module etat0_mod  end module etat0_m

Legend:
Removed from v.178  
changed lines
  Added in v.331

  ViewVC Help
Powered by ViewVC 1.1.21