/[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

revision 99 by guez, Wed Jul 2 18:39:15 2014 UTC revision 129 by guez, Fri Feb 13 18:22:38 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    
# Line 21  contains Line 21  contains
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
# Line 46  contains Line 46  contains
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      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        ! Local:
61    
62      REAL latfi(klon), lonfi(klon)      REAL latfi(klon), lonfi(klon)
63      ! (latitude and longitude of a point of the scalar grid identified      ! (latitude and longitude of a point of the scalar grid identified
# Line 80  contains Line 83  contains
83      real seaice(klon) ! kg m-2      real seaice(klon) ! kg m-2
84      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)
85      REAL rugmer(klon)      REAL rugmer(klon)
     REAL phis(iim + 1, jjm + 1) ! surface geopotential, in m2 s-2  
86      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
87      real, dimension(iim + 1, jjm + 1):: zthe_2d, zpic_2d, zval_2d      real, dimension(iim + 1, jjm + 1):: zthe_2d, zpic_2d, zval_2d
88      real, dimension(iim + 1, jjm + 1):: tsol_2d, qsol_2d, ps      real, dimension(iim + 1, jjm + 1):: tsol_2d, qsol_2d, ps
# Line 121  contains Line 123  contains
123      ! ("p3d(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",      ! ("p3d(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",
124      ! for interface "l")      ! for interface "l")
125    
126        namelist /etat0_nml/ day_ref, annee_ref
127    
128      !---------------------------------      !---------------------------------
129    
130      print *, "Call sequence information: etat0"      print *, "Call sequence information: etat0"
131    
132        print *, "Enter namelist 'etat0_nml'."
133        read(unit=*, nml=etat0_nml)
134        write(unit_nml, nml=etat0_nml)
135    
136      CALL iniconst      CALL iniconst
137    
138      ! Construct a grid:      ! Construct a grid:
# Line 294  contains Line 302  contains
302      ! Calcul interm\'ediaire :      ! Calcul interm\'ediaire :
303      CALL massdair(p3d, masse)      CALL massdair(p3d, masse)
304    
     print *, 'ALPHAX = ', alphax  
   
305      forall (l = 1:llm)      forall (l = 1:llm)
306         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
307         masse(:, jjm + 1, l) = &         masse(:, jjm + 1, l) = &
# Line 305  contains Line 311  contains
311      ! Initialisation pour traceurs:      ! Initialisation pour traceurs:
312      call iniadvtrac      call iniadvtrac
313      itau_phy = 0      itau_phy = 0
     day_ref = dayref  
     annee_ref = anneeref  
314    
315      CALL geopot(teta, pk , pks, phis, phi)      CALL geopot(teta, pk , pks, phis, phi)
316      CALL caldyn0(ucov, vcov, teta, ps, masse, pk, phis, phi, w, pbaru, &      CALL caldyn0(ucov, vcov, teta, ps, masse, pk, phis, phi, w, pbaru, &
317           pbarv)           pbarv)
318      CALL dynredem0("start.nc", dayref, phis)      CALL dynredem0("start.nc", day_ref, phis)
319      CALL dynredem1("start.nc", vcov, ucov, teta, q, masse, ps, itau=0)      CALL dynredem1("start.nc", vcov, ucov, teta, q, masse, ps, itau=0)
320    
321      ! Initialisations :      ! Initialisations :

Legend:
Removed from v.99  
changed lines
  Added in v.129

  ViewVC Help
Powered by ViewVC 1.1.21