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

Diff of /trunk/dyn3d/etat0.f

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

trunk/Sources/dyn3d/etat0.f revision 212 by guez, Thu Jan 12 12:31:31 2017 UTC trunk/dyn3d/etat0.f revision 304 by guez, Thu Sep 6 15:51:09 2018 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    
# Line 21  contains Line 12  contains
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      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, pa, disvert
19      use dynetat0_m, only: day_ref, annee_ref, xprimp025, xprimm025, rlatu1, &      use dynetat0_m, only: day_ref, annee_ref, rlatu, rlatv, rlonu, rlonv, &
20           rlatu2, rlatu, rlatv, yprimu1, yprimu2, rlonu, rlonv, xprimu, xprimv           fyhyp, fxhyp
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 grille_m_m, 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 iniadvtrac_m, only: iniadvtrac
29      use inifilr_m, only: inifilr      use inifilr_m, only: inifilr
30      use massdair_m, only: massdair      use massdair_m, only: massdair
# Line 43  contains Line 32  contains
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, itau_phy      use phyetat0_m, only: zmasq, 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
# Line 59  contains Line 48  contains
48      REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)      REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)
49      ! surface geopotential, in m2 s-2      ! surface geopotential, in m2 s-2
50    
51        REAL, intent(out):: pctsrf(:, :) ! (klon, nbsrf)
52        ! "pctsrf(i, :)" is the composition of the surface at horizontal
53        ! position "i".
54    
55      ! Local:      ! Local:
56    
57      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta
# Line 71  contains Line 64  contains
64    
65      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
66      REAL qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)      REAL qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)
67      REAL albe(klon, nbsrf), evap(klon, nbsrf)      REAL albe(klon, nbsrf)
68      REAL tsoil(klon, nsoilmx, nbsrf)      REAL tsoil(klon, nsoilmx, nbsrf)
69      REAL null_array(klon)      REAL null_array(klon)
70      REAL solsw(klon), sollw(klon)      REAL solsw(klon), sollw(klon)
# Line 91  contains Line 84  contains
84      ! D\'eclarations pour lecture glace de mer :      ! D\'eclarations pour lecture glace de mer :
85      INTEGER iml_lic, jml_lic      INTEGER iml_lic, jml_lic
86      INTEGER ncid, varid      INTEGER ncid, varid
87      REAL, pointer:: dlon_lic(:), dlat_lic(:)      REAL, ALLOCATABLE:: dlon_lic(:), dlat_lic(:)
88      REAL, ALLOCATABLE:: fraclic(:, :) ! fraction land ice      REAL, ALLOCATABLE:: fraclic(:, :) ! fraction land ice
89      REAL flic_tmp(iim + 1, jjm + 1) ! fraction land ice temporary      REAL flic_tmp(iim + 1, jjm + 1) ! fraction land ice temporary
90    
# Line 130  contains Line 123  contains
123      pa = 5e4      pa = 5e4
124      CALL disvert      CALL disvert
125      call test_disvert      call test_disvert
126        CALL fyhyp
127      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)  
   
128      CALL inigeom      CALL inigeom
129      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.  
   
130      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, &
131           zpic_2d, zval_2d) ! also compute "mask"           zpic_2d, zval_2d) ! also compute "mask"
132      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
133      zmasq = pack(mask, dyn_phy)      call phyetat0_new
     PRINT *, 'Masque construit'  
134    
135      call start_init_phys(tsol_2d, qsol_2d)      call start_init_phys(tsol_2d, qsol_2d)
136      CALL start_init_dyn(tsol_2d, phis, ps)      CALL start_init_dyn(tsol_2d, phis, ps)
# Line 261  contains Line 237  contains
237           rlatu)           rlatu)
238      flic_tmp(iim + 1, :) = flic_tmp(1, :)      flic_tmp(iim + 1, :) = flic_tmp(1, :)
239    
240      deallocate(dlon_lic, dlat_lic) ! pointers      ! Passage sur la grille physique :
   
     ! Passage sur la grille physique  
241      pctsrf = 0.      pctsrf = 0.
242      pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy)      pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy)
243      ! Ad\'equation avec le maque terre/mer      
244        ! Ad\'equation avec le maque terre/mer :
245      WHERE (pctsrf(:, is_lic) < EPSFRA) pctsrf(:, is_lic) = 0.      WHERE (pctsrf(:, is_lic) < EPSFRA) pctsrf(:, is_lic) = 0.
246      WHERE (zmasq < EPSFRA) pctsrf(:, is_lic) = 0.      WHERE (zmasq < EPSFRA) pctsrf(:, is_lic) = 0.
247      pctsrf(:, is_ter) = zmasq      where (zmasq <= EPSFRA) pctsrf(:, is_ter) = zmasq
248      where (zmasq > EPSFRA)      where (zmasq > EPSFRA)
249         where (pctsrf(:, is_lic) >= zmasq)         where (pctsrf(:, is_lic) >= zmasq)
250            pctsrf(:, is_lic) = zmasq            pctsrf(:, is_lic) = zmasq
# Line 315  contains Line 290  contains
290      albe(:, is_lic) = 0.6      albe(:, is_lic) = 0.6
291      albe(:, is_oce) = 0.5      albe(:, is_oce) = 0.5
292      albe(:, is_sic) = 0.6      albe(:, is_sic) = 0.6
     evap = 0.  
293      qsolsrf = 150.      qsolsrf = 150.
294      tsoil = spread(spread(pack(tsol_2d, dyn_phy), 2, nsoilmx), 3, nbsrf)      tsoil = spread(spread(pack(tsol_2d, dyn_phy), 2, nsoilmx), 3, nbsrf)
295      solsw = 165.      solsw = 165.
# Line 334  contains Line 308  contains
308      sig1 = 0.      sig1 = 0.
309      w01 = 0.      w01 = 0.
310    
311      nday = 0      nday = 0 ! side effect
     itau_phy = 0 ! side effect  
312      call phyredem0      call phyredem0
313    
314      call nf95_inq_varid(ncid_restartphy, "trs", varid)      call nf95_inq_varid(ncid_restartphy, "trs", varid)
315      call nf95_put_var(ncid_restartphy, varid, null_array)      call nf95_put_var(ncid_restartphy, varid, null_array)
316    
317      call phyredem(pctsrf, tsoil(:, 1, :), tsoil, qsolsrf, &      call phyredem(pctsrf, tsoil(:, 1, :), tsoil, qsolsrf, &
318           pack(qsol_2d, dyn_phy), snsrf, albe, evap, null_array, null_array, &           pack(qsol_2d, dyn_phy), snsrf, albe, null_array, null_array, solsw, &
319           solsw, sollw, null_array, null_array, frugs, agesno, zmea, zstd, &           sollw, null_array, null_array, frugs, agesno, zmea, zstd, zsig, zgam, &
320           zsig, zgam, zthe, zpic, zval, t_ancien, q_ancien, rnebcon, ratqs, &           zthe, zpic, zval, t_ancien, q_ancien, rnebcon, ratqs, clwcon, &
321           clwcon, null_array, sig1, w01)           null_array, sig1, w01)
322    
323    END SUBROUTINE etat0    END SUBROUTINE etat0
324    
325  end module etat0_mod  end module etat0_m

Legend:
Removed from v.212  
changed lines
  Added in v.304

  ViewVC Help
Powered by ViewVC 1.1.21