Ignore:
Timestamp:
Jan 22, 2019, 4:21:59 PM (6 years ago)
Author:
Laurent Fairhead
Message:

"Historic" :-) commit merging the physics branch used for DYNAMICO with the LMDZ trunk.
The same physics branch can now be used seamlessly with the traditional lon-lat LMDZ
dynamical core and DYNAMICO.
Testing consisted in running a lon-lat LMDZ bucket simulation with the NPv6.1 physics package
with the original trunk sources and the merged sources. Tests were succesful in the sense that
numeric continuity was preserved in the restart files from both simulation. Further tests
included running both versions of the physics codes for one year in a LMDZOR setting in which
the restart files also came out identical.

Caution:

  • as the physics package now manages unstructured grids, grid information needs to be transmitted

to the surface scheme ORCHIDEE. This means that the interface defined in surf_land_orchidee_mod.F90
is only compatible with ORCHIDEE version orchidee2.1 and later versions. If previous versions of
ORCHIDEE need to be used, the CPP key ORCHIDEE_NOUNSTRUCT needs to be set at compilation time.
This is done automatically if makelmdz/makelmdz_fcm are called with the veget orchidee2.0 switch

  • due to a limitation in XIOS, the time at which limit conditions will be read in by DYNAMICO will be

delayed by one physic timestep with respect to the time it is read in by the lon-lat model. This is caused
by the line

IF (MOD(itime-1, lmt_pas) == 0 .OR. (jour_lu /= jour .AND. grid_type /= unstructured)) THEN ! time to read

in limit_read_mod.F90

Work still needed on COSP integration and XML files for DYNAMICO

EM, YM, LF

Location:
LMDZ6/trunk/libf/phy_common
Files:
1 added
6 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phy_common/geometry_mod.F90

    r2395 r3435  
    3030!$OMP THREADPRIVATE(cell_area)
    3131
     32  INTEGER,SAVE,ALLOCATABLE :: ind_cell_glo(:)      ! global indice of a local cell
     33!$OMP THREADPRIVATE(ind_cell_glo)
    3234
    3335CONTAINS
     
    3537  SUBROUTINE init_geometry(klon,longitude_,latitude_, &
    3638                           boundslon_,boundslat_, &
    37                            cell_area_,dx_,dy_)
     39                           cell_area_,ind_cell_glo_,dx_,dy_)
    3840  USE mod_grid_phy_lmdz, ONLY: nvertex
    3941  USE nrtype, ONLY : PI
     
    4547    REAL,INTENT(IN) :: boundslat_(klon,nvertex)
    4648    REAL,INTENT(IN) :: cell_area_(klon)
     49    INTEGER,OPTIONAL,INTENT(IN) :: ind_cell_glo_(klon)
    4750    REAL,OPTIONAL,INTENT(IN) :: dx_(klon)
    4851    REAL,OPTIONAL,INTENT(IN) :: dy_(klon)
     
    5558    ALLOCATE(boundslat(klon,nvertex))
    5659    ALLOCATE(cell_area(klon))
     60    IF (PRESENT(ind_cell_glo_)) ALLOCATE(ind_cell_glo(klon))
    5761    IF (PRESENT(dx_)) ALLOCATE(dx(klon))
    5862    IF (PRESENT(dy_))ALLOCATE(dy(klon))
     
    6569    boundslat(:,:) = boundslat_(:,:)
    6670    cell_area(:) = cell_area_(:)
     71    IF (PRESENT(ind_cell_glo_)) ind_cell_glo(:) = ind_cell_glo_(:)
    6772    IF (PRESENT(dx_)) dx(:) = dx_(:)
    6873    IF (PRESENT(dy_)) dy(:) = dy_(:)
  • LMDZ6/trunk/libf/phy_common/mod_phys_lmdz_mpi_data.F90

    r2429 r3435  
    33!
    44MODULE mod_phys_lmdz_mpi_data
    5 !  USE mod_const_mpi
    65 
    76  INTEGER,SAVE :: ii_begin
     
    3635  INTEGER,SAVE :: mpi_size
    3736  INTEGER,SAVE :: mpi_master
    38 !  INTEGER,SAVE :: mpi_root
    3937  LOGICAL,SAVE :: is_mpi_root
    4038  LOGICAL,SAVE :: is_using_mpi
    4139 
    4240 
    43 !  LOGICAL,SAVE :: is_north_pole
    44 !  LOGICAL,SAVE :: is_south_pole
    4541  LOGICAL,SAVE :: is_north_pole_dyn
    4642  LOGICAL,SAVE :: is_south_pole_dyn
     
    5046CONTAINS
    5147 
    52 !  SUBROUTINE Init_phys_lmdz_mpi_data(iim,jjp1,nb_proc,distrib)
    5348  SUBROUTINE init_phys_lmdz_mpi_data(nbp, nbp_lon, nbp_lat, communicator)
    54 !  USE mod_const_mpi, ONLY : COMM_LMDZ
    5549  IMPLICIT NONE
    5650#ifdef CPP_MPI
    5751    INCLUDE 'mpif.h'
    5852#endif
    59     INTEGER,INTENT(in) :: nbp
    60     INTEGER,INTENT(in) :: nbp_lon
    61     INTEGER,INTENT(in) :: nbp_lat
    62     INTEGER,INTENT(in) :: communicator
     53    INTEGER,INTENT(IN) :: nbp
     54    INTEGER,INTENT(IN) :: nbp_lon
     55    INTEGER,INTENT(IN) :: nbp_lat
     56    INTEGER,INTENT(IN) :: communicator
    6357   
    6458    INTEGER,ALLOCATABLE :: distrib(:)
     
    189183
    190184  SUBROUTINE print_module_data
    191 !  USE print_control_mod, ONLY: lunout
     185  USE print_control_mod, ONLY: lunout
    192186  IMPLICIT NONE
    193   INCLUDE "iniprint.h"
     187!  INCLUDE "iniprint.h"
    194188 
    195189    WRITE(lunout,*) 'ii_begin =', ii_begin
  • LMDZ6/trunk/libf/phy_common/mod_phys_lmdz_omp_data.F90

    r2429 r3435  
    77  INTEGER,SAVE :: omp_rank
    88  LOGICAL,SAVE :: is_omp_root
     9  LOGICAL,SAVE :: is_omp_master  ! alias of is_omp_root
    910  LOGICAL,SAVE :: is_using_omp
    1011  LOGICAL,SAVE :: is_north_pole_phy, is_south_pole_phy
     
    1718  INTEGER,SAVE :: klon_omp_begin
    1819  INTEGER,SAVE :: klon_omp_end
    19 !$OMP  THREADPRIVATE(omp_rank,klon_omp,is_omp_root,klon_omp_begin,klon_omp_end)
     20!$OMP  THREADPRIVATE(omp_rank,klon_omp,is_omp_root,is_omp_master,klon_omp_begin,klon_omp_end)
    2021!$OMP  THREADPRIVATE(is_north_pole_phy, is_south_pole_phy)
    2122
     
    6061   ELSE
    6162     abort_message = 'ANORMAL : OMP_MASTER /= 0'
    62      CALL abort_gcm (modname,abort_message,1)
     63     CALL abort_physic (modname,abort_message,1)
    6364   ENDIF
    6465!$OMP END MASTER
    65 
     66   is_omp_master=is_omp_root
    6667
    6768!$OMP MASTER
     
    106107
    107108  SUBROUTINE Print_module_data
     109  USE print_control_mod, ONLY: lunout
    108110  IMPLICIT NONE
    109   INCLUDE "iniprint.h"
     111!  INCLUDE "iniprint.h"
    110112
    111113!$OMP CRITICAL 
  • LMDZ6/trunk/libf/phy_common/mod_phys_lmdz_para.F90

    r2429 r3435  
    4949  SUBROUTINE Test_transfert
    5050  USE mod_grid_phy_lmdz
     51  USE print_control_mod, ONLY: lunout
    5152  IMPLICIT NONE
    52     INCLUDE "iniprint.h"
     53!    INCLUDE "iniprint.h"
    5354 
    5455    REAL :: Test_Field1d_glo(klon_glo,nbp_lev)
  • LMDZ6/trunk/libf/phy_common/physics_distribution_mod.F90

    r2351 r3435  
    1010                                       nbp, nbp_lon, nbp_lat, nbp_lev, &
    1111                                       communicator)
    12   USE mod_phys_lmdz_para, ONLY: init_phys_lmdz_para
     12  USE mod_phys_lmdz_para, ONLY: init_phys_lmdz_para, klon_omp
    1313  USE mod_grid_phy_lmdz, ONLY: init_grid_phy_lmdz
     14  USE dimphy, ONLY : Init_dimphy
     15  USE infotrac_phy, ONLY : type_trac
     16#ifdef REPROBUS
     17  USE CHEM_REP, ONLY : Init_chem_rep_phys
     18#endif
     19
    1420  IMPLICIT NONE
    1521    INTEGER,INTENT(IN) :: grid_type
     
    2430    CALL init_grid_phy_lmdz(grid_type,nvertex, nbp_lon,nbp_lat,nbp_lev)
    2531    CALL init_phys_lmdz_para(nbp,nbp_lon, nbp_lat, communicator)
     32!$OMP PARALLEL
     33    CALL init_dimphy(klon_omp,nbp_lev)
     34
     35! Initialization of Reprobus
     36    IF (type_trac == 'repr') THEN
     37#ifdef REPROBUS
     38       CALL Init_chem_rep_phys(klon_omp,nbp_lev)
     39#endif
     40    END IF
     41
     42!$OMP END PARALLEL
    2643
    2744  END SUBROUTINE init_physics_distribution 
  • LMDZ6/trunk/libf/phy_common/print_control_mod.F90

    r2326 r3435  
    77!$OMP THREADPRIVATE(lunout,prt_level,debug)
    88
     9  ! NB: Module variable Initializations done by set_print_control
     10  !     routine from init_print_control_mod to avoid circular
     11  !     module dependencies
     12
    913CONTAINS
    1014
    11   SUBROUTINE init_print_control
    12   USE ioipsl_getin_p_mod, ONLY : getin_p
    13   USE mod_phys_lmdz_para, ONLY: is_omp_root, is_master
     15  SUBROUTINE set_print_control(lunout_,prt_level_,debug_)
    1416  IMPLICIT NONE
    15 
    16     LOGICAL :: opened
    17     INTEGER :: number
     17    INTEGER :: lunout_
     18    INTEGER :: prt_level_
     19    LOGICAL :: debug_
     20     
     21    lunout = lunout_
     22    prt_level = prt_level_
     23    debug = debug_
    1824   
    19     !Config  Key  = prt_level
    20     !Config  Desc = niveau d'impressions de débogage
    21     !Config  Def  = 0
    22     !Config  Help = Niveau d'impression pour le débogage
    23     !Config         (0 = minimum d'impression)
    24     prt_level = 0
    25     CALL getin_p('prt_level',prt_level)
    26 
    27     !Config  Key  = lunout
    28     !Config  Desc = unite de fichier pour les impressions
    29     !Config  Def  = 6
    30     !Config  Help = unite de fichier pour les impressions
    31     !Config         (defaut sortie standard = 6)
    32     lunout=6
    33     CALL getin_p('lunout', lunout)
    34 
    35     IF (is_omp_root) THEN
    36       IF (lunout /= 5 .and. lunout /= 6) THEN
    37          INQUIRE(FILE='lmdz.out_0000',OPENED=opened,NUMBER=number)
    38          IF (opened) THEN
    39            lunout=number
    40          ELSE
    41            OPEN(UNIT=lunout,FILE='lmdz.out_0000',ACTION='write',  &
    42                 STATUS='unknown',FORM='formatted')
    43          ENDIF
    44       ENDIF
    45     ENDIF
    46 
    47     !Config  Key  = debug
    48     !Config  Desc = mode debogage
    49     !Config  Def  = false
    50     !Config  Help = positionne le mode debogage
    51 
    52     debug = .FALSE.
    53     CALL getin_p('debug',debug)
    54    
    55     IF (is_master) THEN
    56       WRITE(lunout,*)"init_print_control: prt_level=",prt_level
    57       WRITE(lunout,*)"init_print_control: lunout=",lunout
    58       WRITE(lunout,*)"init_print_control: debug=",debug     
    59     ENDIF
    60    
    61   END SUBROUTINE init_print_control 
     25  END SUBROUTINE set_print_control
    6226
    6327END MODULE print_control_mod
Note: See TracChangeset for help on using the changeset viewer.