Ignore:
Timestamp:
Sep 29, 2016, 11:26:46 PM (8 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes r2593:2640 into testing branch

Location:
LMDZ5/branches/testing
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/dynphy_lonlat/phylmd/callphysiq_mod.F90

    r2435 r2641  
    1212                       jD_cur,jH_cur_split,zdt_split,                     &
    1313                       zplev_omp,zplay_omp,                               &
    14                        zphi_omp,zphis_omp,                                &
     14                       zpk_omp,zphi_omp,zphis_omp,                        &
    1515                       presnivs_omp,                                      &
    1616                       zufi_omp,zvfi_omp,zrfi_omp,ztfi_omp,zqfi_omp,      &
     
    3535  REAL,INTENT(IN) :: zplev_omp(klon,llm+1) ! interlayer pressure (Pa)
    3636  REAL,INTENT(IN) :: zplay_omp(klon,llm) ! mid-layer pressure (Pa)
     37  REAL,INTENT(IN) :: zpk_omp(klon,llm) ! Exner function
    3738  REAL,INTENT(IN) :: zphi_omp(klon,llm) ! geopotential at midlayer
    3839  REAL,INTENT(IN) :: zphis_omp(klon) ! surface geopotential
  • LMDZ5/branches/testing/libf/dynphy_lonlat/phylmd/ce0l.F90

    r2471 r2641  
    3434  USE mod_interface_dyn_phys, ONLY: init_interface_dyn_phys
    3535#endif
     36  USE comconst_mod, ONLY: cpp, daysec, dtphys, dtvr, g, kappa, omeg, r, rad, &
     37                          pi, jmp1
     38  USE logic_mod, ONLY: iflag_phys, ok_etat0, ok_limit
     39  USE comvert_mod, ONLY: pa, preff, pressure_exner
     40  USE temps_mod, ONLY: calend, day_ini, dt
    3641
    3742  IMPLICIT NONE
     
    4247  include "paramet.h"
    4348  include "comgeom2.h"
    44   include "comconst.h"
    45   include "comvert.h"
    4649  include "iniprint.h"
    47   include "temps.h"
    48   include "logic.h"
    4950  REAL               :: masque(iip1,jjp1)             !--- CONTINENTAL MASK
    5051  REAL               :: phis  (iip1,jjp1)             !--- GROUND GEOPOTENTIAL
  • LMDZ5/branches/testing/libf/dynphy_lonlat/phylmd/etat0dyn_netcdf.F90

    r2435 r2641  
    3636  USE ioipsl,         ONLY: flininfo, flinopen, flinget, flinclo, histclo
    3737  USE assert_eq_m,    ONLY: assert_eq
     38  USE comconst_mod, ONLY: pi, cpp, kappa
     39  USE comvert_mod, ONLY: ap, bp, preff, pressure_exner
     40  USE temps_mod, ONLY: annee_ref, day_ref, itau_dyn, itau_phy
     41 
    3842  IMPLICIT NONE
    3943
     
    4549  include "paramet.h"
    4650  include "comgeom2.h"
    47   include "comvert.h"
    48   include "comconst.h"
    49   include "temps.h"
    5051  include "comdissnew.h"
    51   include "serre.h"
    5252  REAL, SAVE :: deg2rad
    5353  INTEGER,            SAVE      :: iml_dyn, jml_dyn, llm_dyn, ttm_dyn, fid_dyn
  • LMDZ5/branches/testing/libf/dynphy_lonlat/phylmd/etat0phys_netcdf.F90

    r2542 r2641  
    4444    zmax0,fevap, rnebcon,falb_dir, wake_fip,    agesno,  detr_therm, pbl_tke,  &
    4545    phys_state_var_init
     46  USE comconst_mod, ONLY: pi, dtvr
    4647
    4748  PRIVATE
     
    5253  include "paramet.h"
    5354  include "comgeom2.h"
    54   include "comconst.h"
    5555  include "dimsoil.h"
    56   include "temps.h"
    5756  include "clesphys.h"
    5857  REAL, SAVE :: deg2rad
  • LMDZ5/branches/testing/libf/dynphy_lonlat/phylmd/iniphysiq_mod.F90

    r2594 r2641  
    1212                     prad,pg,pr,pcpp,iflag_phys)
    1313  USE dimphy, ONLY: init_dimphy
     14  USE comvert_mod, ONLY: preff, ap, bp, presnivs, scaleheight, pseudoalt
    1415  USE inigeomphy_mod, ONLY: inigeomphy
    15   USE mod_grid_phy_lmdz, ONLY: klon_glo ! number of atmospheric columns (on full grid)
     16  USE mod_grid_phy_lmdz, ONLY: nbp_lon,nbp_lat,nbp_lev,klon_glo ! number of atmospheric columns (on full grid)
    1617  USE mod_phys_lmdz_para, ONLY: klon_omp ! number of columns (on local omp grid)
    1718  USE vertical_layers_mod, ONLY : init_vertical_layers
     
    2829  USE CHEM_REP, ONLY : Init_chem_rep_phys
    2930#endif
    30   USE control_mod, ONLY: dayref,anneeref,day_step,nday,offline, iphysiq
     31  USE control_mod, ONLY: dayref,anneeref,day_step,nday,offline, iphysiq, config_inca
    3132  USE inifis_mod, ONLY: inifis
    3233  USE time_phylmdz_mod, ONLY: init_time
     34  USE temps_mod, ONLY: annee_ref, day_ini, day_ref, start_time, calend
    3335  USE infotrac_phy, ONLY: init_infotrac_phy
    3436  USE phystokenc_mod, ONLY: init_phystokenc
     
    5052
    5153  include "dimensions.h"
    52   include "comvert.h"
    53   include "comconst.h"
    5454  include "iniprint.h"
    55   include "temps.h"
    5655  include "tracstoke.h"
    5756
     
    9998  ! --> now initialize things specific to the phylmd physics package
    10099 
    101 !$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/)
     100!!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/)
     101!$OMP PARALLEL DEFAULT(SHARED) &
     102!       Copy all threadprivate variables in temps_mod
     103!$OMP COPYIN(annee_ref, day_ini, day_ref, start_time)
    102104
    103105  ! copy over preff , ap(), bp(), etc
     
    139141     call init_const_lmdz( &
    140142          anneeref,dayref, iphysiq,day_step,nday,  &
    141           nbsrf, is_oce,is_sic, is_ter,is_lic, calend)
     143          nbsrf, is_oce,is_sic, is_ter,is_lic, calend, &
     144          config_inca)
    142145     call init_inca_para( &
    143146          nbp_lon,nbp_lat,nbp_lev,klon_glo,mpi_size, &
     
    145148#endif
    146149  END IF
    147 !$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/)
    148150
     151!!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/)
     152!$OMP PARALLEL DEFAULT(SHARED)
    149153  ! Additional initializations for aquaplanets
    150154  IF (iflag_phys>=100) THEN
  • LMDZ5/branches/testing/libf/dynphy_lonlat/phylmd/init_ssrf_m.F90

    r2435 r2641  
    99  USE grid_atob_m,        ONLY: grille_m
    1010  USE ioipsl,             ONLY: flininfo, flinopen, flinget, flinclo
     11  USE comconst_mod, ONLY: im, pi
    1112
    1213  CHARACTER(LEN=256), PARAMETER :: icefname="landiceref.nc", icevar="landice"
     
    1718  include "paramet.h"
    1819  include "comgeom2.h"
    19   include "comconst.h"
    2020
    2121CONTAINS
  • LMDZ5/branches/testing/libf/dynphy_lonlat/phylmd/limit_netcdf.F90

    r2594 r2641  
    6767                  NF90_DEF_DIM, NF90_DEF_VAR, NF90_PUT_VAR, NF90_PUT_ATT,      &
    6868                  NF90_NOERR,   NF90_NOWRITE, NF90_DOUBLE,  NF90_GLOBAL,       &
    69                   NF90_CLOBBER, NF90_ENDDEF,  NF90_UNLIMITED, NF90_FLOAT
     69                  NF90_CLOBBER, NF90_ENDDEF,  NF90_UNLIMITED, NF90_FLOAT
    7070  USE inter_barxy_m,      ONLY: inter_barxy
    7171  USE netcdf95,           ONLY: nf95_def_var, nf95_put_att, nf95_put_var
     72  USE comconst_mod, ONLY: pi
    7273  IMPLICIT NONE
    7374!-------------------------------------------------------------------------------
     
    8182!-------------------------------------------------------------------------------
    8283! Local variables:
    83   include "logic.h"
    8484  include "comgeom2.h"
    85   include "comconst.h"
    8685
    8786!--- INPUT NETCDF FILES NAMES --------------------------------------------------
  • LMDZ5/branches/testing/libf/dynphy_lonlat/phylmd/test_disvert_m.F90

    r2435 r2641  
    1515    use exner_hyb_m, only: exner_hyb
    1616    use vertical_layers_mod, only: ap,bp,preff
     17    use comconst_mod, only: kappa, cpp
    1718
    1819    ! For llm:
    1920    include "dimensions.h"
    20 
    21     ! For kappa, cpp:
    22     include "comconst.h"
    2321
    2422    ! Local:
Note: See TracChangeset for help on using the changeset viewer.