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

Diff of /trunk/dyn3d/etat0.f90

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

revision 163 by guez, Fri Jul 24 18:14:04 2015 UTC revision 225 by guez, Mon Oct 16 12:35:41 2017 UTC
# Line 20  contains Line 20  contains
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: aire_2d, apoln, apols, cu_2d, cv_2d, inigeom      use comgeom, only: aire_2d, apoln, apols, cu_2d, cv_2d, inigeom
23      use conf_gcm_m, only: nday, day_step, iphysiq      use conf_gcm_m, only: nday
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
# Line 33  contains Line 33  contains
33      use fxhyp_m, only: fxhyp      use fxhyp_m, only: fxhyp
34      use fyhyp_m, only: fyhyp      use fyhyp_m, only: fyhyp
35      use geopot_m, only: geopot      use geopot_m, only: geopot
36      use grid_atob, only: grille_m      use grille_m_m, only: grille_m
37      use grid_change, only: init_dyn_phy, dyn_phy      use grid_change, only: init_dyn_phy, dyn_phy
38      use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra      use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra
39      use iniadvtrac_m, only: iniadvtrac      use iniadvtrac_m, only: iniadvtrac
# Line 43  contains Line 43  contains
43      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, &
44           nf95_inq_varid, nf95_open           nf95_inq_varid, nf95_open
45      use nr_util, only: pi, assert      use nr_util, only: pi, assert
46      use paramet_m, only: ip1jm, ip1jmp1      use phyetat0_m, only: rlat, rlon, itau_phy
     use phyetat0_m, only: rlat, rlon  
47      use phyredem0_m, only: phyredem0, ncid_restartphy      use phyredem0_m, only: phyredem0, ncid_restartphy
48      use phyredem_m, only: phyredem      use phyredem_m, only: phyredem
49      use q_sat_m, only: q_sat      use q_sat_m, only: q_sat
# Line 54  contains Line 53  contains
53      USE start_init_orog_m, only: start_init_orog, mask      USE start_init_orog_m, only: start_init_orog, mask
54      use start_init_phys_m, only: start_init_phys      use start_init_phys_m, only: start_init_phys
55      use start_inter_3d_m, only: start_inter_3d      use start_inter_3d_m, only: start_inter_3d
     use temps, only: itau_phy  
56      use test_disvert_m, only: test_disvert      use test_disvert_m, only: test_disvert
57      use unit_nml_m, only: unit_nml      use unit_nml_m, only: unit_nml
58    
# Line 93  contains Line 91  contains
91      ! D\'eclarations pour lecture glace de mer :      ! D\'eclarations pour lecture glace de mer :
92      INTEGER iml_lic, jml_lic      INTEGER iml_lic, jml_lic
93      INTEGER ncid, varid      INTEGER ncid, varid
94      REAL, pointer:: dlon_lic(:), dlat_lic(:)      REAL, ALLOCATABLE:: dlon_lic(:), dlat_lic(:)
95      REAL, ALLOCATABLE:: fraclic(:, :) ! fraction land ice      REAL, ALLOCATABLE:: fraclic(:, :) ! fraction land ice
96      REAL flic_tmp(iim + 1, jjm + 1) ! fraction land ice temporary      REAL flic_tmp(iim + 1, jjm + 1) ! fraction land ice temporary
97    
# Line 263  contains Line 261  contains
261           rlatu)           rlatu)
262      flic_tmp(iim + 1, :) = flic_tmp(1, :)      flic_tmp(iim + 1, :) = flic_tmp(1, :)
263    
     deallocate(dlon_lic, dlat_lic) ! pointers  
   
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\'equation 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      where (zmasq <= EPSFRA) pctsrf(:, is_ter) = zmasq
271      where (zmasq > EPSFRA)      where (zmasq > EPSFRA)
272         where (pctsrf(:, is_lic) >= zmasq)         where (pctsrf(:, is_lic) >= zmasq)
273            pctsrf(:, is_lic) = zmasq            pctsrf(:, is_lic) = zmasq
# Line 336  contains Line 332  contains
332      sig1 = 0.      sig1 = 0.
333      w01 = 0.      w01 = 0.
334    
     itau_phy = 0  
335      nday = 0      nday = 0
336      call phyredem0(lmt_pas = day_step / iphysiq)      itau_phy = 0 ! side effect
337        call phyredem0
338    
339      call nf95_inq_varid(ncid_restartphy, "trs", varid)      call nf95_inq_varid(ncid_restartphy, "trs", varid)
340      call nf95_put_var(ncid_restartphy, varid, null_array)      call nf95_put_var(ncid_restartphy, varid, null_array)
341    
342      call phyredem(pctsrf, tsoil(:, 1, :), tsoil, tsoil(:, 1, is_oce), &      call phyredem(pctsrf, tsoil(:, 1, :), tsoil, qsolsrf, &
343           null_array, qsolsrf, pack(qsol_2d, dyn_phy), snsrf, albe, evap, &           pack(qsol_2d, dyn_phy), snsrf, albe, evap, null_array, null_array, &
344           null_array, null_array, solsw, sollw, null_array, null_array, frugs, &           solsw, sollw, null_array, null_array, frugs, agesno, zmea, zstd, &
345           agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, &           zsig, zgam, zthe, zpic, zval, t_ancien, q_ancien, rnebcon, ratqs, &
346           q_ancien, rnebcon, ratqs, clwcon, null_array, sig1, w01)           clwcon, null_array, sig1, w01)
347    
348    END SUBROUTINE etat0    END SUBROUTINE etat0
349    

Legend:
Removed from v.163  
changed lines
  Added in v.225

  ViewVC Help
Powered by ViewVC 1.1.21