/[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 279 by guez, Fri Jul 20 14:30:23 2018 UTC revision 313 by guez, Mon Dec 10 15:54:30 2018 UTC
# Line 15  contains Line 15  contains
15      use dimensions, only: iim, jjm, llm, nqmx      use dimensions, only: iim, jjm, llm, nqmx
16      use dimphy, only: klon      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, rlatu, rlatv, rlonu, rlonv, &      use dynetat0_m, only: rlatu, rlatv, rlonu, rlonv, fyhyp, fxhyp
20           fyhyp, fxhyp      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
# Line 43  contains Line 43  contains
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
# Line 64  contains Line 63  contains
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), snsrf(klon, nbsrf)
66      REAL albe(klon, nbsrf), evap(klon, nbsrf)      REAL albe(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 106  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      CALL fyhyp
# Line 290  contains Line 282  contains
282      albe(:, is_lic) = 0.6      albe(:, is_lic) = 0.6
283      albe(:, is_oce) = 0.5      albe(:, is_oce) = 0.5
284      albe(:, is_sic) = 0.6      albe(:, 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 309  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      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), snsrf, albe, 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    

Legend:
Removed from v.279  
changed lines
  Added in v.313

  ViewVC Help
Powered by ViewVC 1.1.21