Changeset 1682 for trunk/LMDZ.GENERIC


Ignore:
Timestamp:
Mar 31, 2017, 11:31:38 AM (8 years ago)
Author:
emillour
Message:

All GCMs: set things up to enable pluging physics with dynamico

  • dyn3d
  • gcm.F90 : move I/O initialization (dates) to be done before physics

initialization

  • dyn3dpar
  • gcm.F : move I/O initialization (dates) to be done before physics

initialization

  • dynphy_lonlat:
  • inigeomphy_mod.F90 : add ind_cell_glo computation and transfer

to init_geometry

  • phy_common:
  • geometry_mod.F90 : add ind_cell_glo module variable to store global

column index

  • print_control_mod.F90 : make initialization occur via init_print_control_mod

to avoid circular module dependencies

  • init_print_control_mod.F90 : added to initialize print_control_mod module

variables

  • mod_phys_lmdz_mpi_data.F90 : use print_control_mod (rather than iniprint.h)
  • mod_phys_lmdz_para.F90 : use print_control_mod (rather than iniprint.h)
  • mod_phys_lmdz_omp_data.F90 : add is_omp_master (alias of is_omp_root) module

variable and use print_control_mod (rather than
iniprint.h)

  • physics_distribution_mod.F90 : add call to init_dimphy in

init_physics_distribution

  • xios_writefield.F90 : generic routine to output field with XIOS (for debug)
  • misc:
  • handle_err_m.F90 : call abort_physic, rather than abort_gcm
  • wxios.F90 : updates to enable unstructured grids

set module variable g_ctx_name to "LMDZ"
wxios_init(): remove call to wxios_context_init
wxios_context_init(): call xios_context_initialize with COMM_LMDZ_PHY
add routine wxios_set_context() to get handle and set context to XIOS
wxios_domain_param(): change arguments and generate the domain in-place
add wxios_domain_param_unstructured(): generate domain for unstructured case

NB: access is via "domain group" (whereas it is via "domain" in

wxios_domain_param)

  • dynphy_lonlat/phy[std|mars|venus|titan]:
  • iniphysiq_mod.F90 : Remove call to init_dimphy (which is now done in

phy_common/physics_distribution_mod.F90)

EM

Location:
trunk/LMDZ.GENERIC
Files:
1 added
14 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/README

    r1673 r1682  
    12951295>> Followup on updates in LMDZ.COMMON, add print_control_mod.F90
    12961296   and abort_physic.F90 inphy_common
     1297
     1298== 30/03/2017 == EM
     1299>> Keep up with updates in LMDZ.COMMON:
     1300In phystd:
     1301- ocean_slab_mod.F90 : call abort_physic, rather than abort_gcm
     1302- inifis_mod.F90 : initialize print_control variables
     1303- physiq_mod.F90 : add XIOS context initialization and finalization
     1304- xios_output_mod.F90 : update initialize_xios_output initialization
     1305                        of the horizontal domain
     1306In dynphy_lonlat :
     1307- inigeomphy_mod.F90 : add ind_cell_glo computation and  transfer
     1308                       to init_geometry
     1309- mod_interface_dyn_phys.F90 : use is_north_pole_dyn and is_south_pole_dyn
     1310                               (instead of is_north_pole, is_south_pole)
     1311
     1312In phy_common:
     1313- geometry_mod.F90 : add ind_cell_glo module variable to store global
     1314                     column index
     1315- init_print_control_mod.F90 : added to initialize print_control_mod module
     1316                               variables
     1317- print_control_mod.F90 : make initialization occur via init_print_control_mod
     1318                          to avoid circular module dependencies
     1319- mod_phys_lmdz_mpi_data.F90 : use print_control_mod (rather than iniprint.h)
     1320                               and define is_north_pole_dyn, is_south_pole_dyn
     1321                               (instead of is_north_pole, is_south_pole)
     1322- mod_phys_lmdz_mpi_transfert.F90 : use is_north_pole_dyn, is_south_pole_dyn
     1323                                    (instead of is_north_pole, is_south_pole)
     1324- mod_phys_lmdz_omp_data.F90 : add is_omp_master (alias of is_omp_root) module
     1325                               variable and use print_control_mod (rather than
     1326                               iniprint.h), and introduce is_north_pole_phy
     1327                               and is_south_pole_phy
     1328- mod_phys_lmdz_para.F90 : use print_control_mod (rather than iniprint.h)
     1329- physics_distribution_mod.F90 : add call to init_dimphy in
     1330                                 init_physics_distribution
  • trunk/LMDZ.GENERIC/libf/dynphy_lonlat/inigeomphy_mod.F90

    r1621 r1682  
    7373  REAL,ALLOCATABLE,SAVE :: boundslonfi(:,:)
    7474  REAL,ALLOCATABLE,SAVE :: boundslatfi(:,:)
    75 !$OMP THREADPRIVATE (latfi,lonfi,cufi,cvfi,airefi,boundslonfi,boundslatfi)
     75  INTEGER,ALLOCATABLE,SAVE :: ind_cell_glo_fi(:)
     76!$OMP THREADPRIVATE (latfi,lonfi,cufi,cvfi,airefi,boundslonfi,boundslatfi,ind_cell_glo_fi)
    7677
    7778  ! Initialize Physics distibution and parameters and interface with dynamics
     
    201202  ALLOCATE(boundslonfi(klon_omp,4))
    202203  ALLOCATE(boundslatfi(klon_omp,4))
    203 !  CALL initcomgeomphy
     204  ALLOCATE(ind_cell_glo_fi(klon_omp))
     205
    204206
    205207  offset = klon_mpi_begin - 1
     
    211213  boundslonfi(1:klon_omp,:) = boundslonfi_glo(offset+klon_omp_begin:offset+klon_omp_end,:)
    212214  boundslatfi(1:klon_omp,:) = boundslatfi_glo(offset+klon_omp_begin:offset+klon_omp_end,:)
     215  ind_cell_glo_fi(1:klon_omp)=(/ (i,i=offset+klon_omp_begin,offset+klon_omp_end) /)
    213216
    214217  ! copy over local grid longitudes and latitudes
    215218  CALL init_geometry(klon_omp,lonfi,latfi,boundslonfi,boundslatfi, &
    216                      airefi,cufi,cvfi)
     219                     airefi,ind_cell_glo_fi,cufi,cvfi)
    217220
    218221  ! copy over preff , ap(), bp(), etc
  • trunk/LMDZ.GENERIC/libf/dynphy_lonlat/mod_interface_dyn_phys.F90

    r1543 r1682  
    2222   
    2323    k=1
    24     IF (is_north_pole) THEN
     24    IF (is_north_pole_dyn) THEN
    2525      index_i(k)=1
    2626      index_j(k)=1
     
    4242    ENDDO
    4343   
    44     IF (is_south_pole) THEN
     44    IF (is_south_pole_dyn) THEN
    4545      index_i(k)=1
    4646      index_j(k)=jj_end
  • trunk/LMDZ.GENERIC/libf/dynphy_lonlat/phystd/iniphysiq_mod.F90

    r1573 r1682  
    7373! and do some initializations
    7474
    75 ! Initialize dimphy module
    76 call init_dimphy(klon_omp,nlayer)
     75! Initialize dimphy module => Now done in physics_distribution_mod
     76! call init_dimphy(klon_omp,nlayer)
    7777
    7878! copy over preff , ap() and bp()
  • trunk/LMDZ.GENERIC/libf/phy_common/geometry_mod.F90

    r1543 r1682  
    3030!$OMP THREADPRIVATE(cell_area)
    3131
     32  INTEGER,SAVE,ALLOCATABLE :: ind_cell_glo(:)      ! global index 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_(:)
  • trunk/LMDZ.GENERIC/libf/phy_common/mod_phys_lmdz_mpi_data.F90

    r1543 r1682  
    11!
    2 !$Header$
     2!$Id$
    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
     41  LOGICAL,SAVE :: is_north_pole_dyn
     42  LOGICAL,SAVE :: is_south_pole_dyn
    4543  INTEGER,SAVE :: COMM_LMDZ_PHY
    4644  INTEGER,SAVE :: MPI_REAL_LMDZ   ! MPI_REAL8
     
    4846CONTAINS
    4947 
    50 !  SUBROUTINE Init_phys_lmdz_mpi_data(iim,jjp1,nb_proc,distrib)
    5148  SUBROUTINE init_phys_lmdz_mpi_data(nbp, nbp_lon, nbp_lat, communicator)
    52 !  USE mod_const_mpi, ONLY : COMM_LMDZ
    5349  IMPLICIT NONE
    5450#ifdef CPP_MPI
    5551    INCLUDE 'mpif.h'
    5652#endif
    57     INTEGER,INTENT(in) :: nbp
    58     INTEGER,INTENT(in) :: nbp_lon
    59     INTEGER,INTENT(in) :: nbp_lat
    60     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
    6157   
    6258    INTEGER,ALLOCATABLE :: distrib(:)
     
    109105   
    110106    IF (mpi_rank == 0) THEN
    111       is_north_pole = .TRUE.
    112     ELSE
    113       is_north_pole = .FALSE.
     107      is_north_pole_dyn = .TRUE.
     108    ELSE
     109      is_north_pole_dyn = .FALSE.
    114110    ENDIF
    115111   
    116112    IF (mpi_rank == mpi_size-1) THEN
    117       is_south_pole = .TRUE.
    118     ELSE
    119       is_south_pole = .FALSE.
     113      is_south_pole_dyn = .TRUE.
     114    ELSE
     115      is_south_pole_dyn = .FALSE.
    120116    ENDIF
    121117   
     
    187183
    188184  SUBROUTINE print_module_data
    189 !  USE print_control_mod, ONLY: lunout
     185  USE print_control_mod, ONLY: lunout
    190186  IMPLICIT NONE
    191   INCLUDE "iniprint.h"
    192187 
    193188    WRITE(lunout,*) 'ii_begin =', ii_begin
     
    217212    WRITE(lunout,*) 'mpi_master =', mpi_master
    218213    WRITE(lunout,*) 'is_mpi_root =', is_mpi_root
    219     WRITE(lunout,*) 'is_north_pole =', is_north_pole
    220     WRITE(lunout,*) 'is_south_pole =', is_south_pole
     214    WRITE(lunout,*) 'is_north_pole_dyn =', is_north_pole_dyn
     215    WRITE(lunout,*) 'is_south_pole_dyn =', is_south_pole_dyn
    221216    WRITE(lunout,*) 'COMM_LMDZ_PHY =', COMM_LMDZ_PHY
    222217 
  • trunk/LMDZ.GENERIC/libf/phy_common/mod_phys_lmdz_mpi_transfert.F90

    r1543 r1682  
    11!
    2 !$Header$
     2!$Id$
    33!
    44MODULE mod_phys_lmdz_mpi_transfert
     
    16931693   
    16941694    offset=ii_begin
    1695     IF (is_north_pole) Offset=nbp_lon
     1695    IF (is_north_pole_dyn) Offset=nbp_lon
    16961696   
    16971697   
     
    17031703   
    17041704   
    1705     IF (is_north_pole) THEN
     1705    IF (is_north_pole_dyn) THEN
    17061706      DO i=1,dimsize
    17071707        DO ij=1,nbp_lon
     
    17111711    ENDIF
    17121712   
    1713     IF (is_south_pole) THEN
     1713    IF (is_south_pole_dyn) THEN
    17141714      DO i=1,dimsize
    17151715        DO ij=nbp_lon*(jj_nb-1)+1,nbp_lon*jj_nb
     
    17371737   
    17381738    offset=ii_begin
    1739     IF (is_north_pole) Offset=nbp_lon
     1739    IF (is_north_pole_dyn) Offset=nbp_lon
    17401740   
    17411741   
     
    17471747   
    17481748   
    1749     IF (is_north_pole) THEN
     1749    IF (is_north_pole_dyn) THEN
    17501750      DO i=1,dimsize
    17511751        DO ij=1,nbp_lon
     
    17551755    ENDIF
    17561756   
    1757     IF (is_south_pole) THEN
     1757    IF (is_south_pole_dyn) THEN
    17581758      DO i=1,dimsize
    17591759        DO ij=nbp_lon*(jj_nb-1)+1,nbp_lon*jj_nb
     
    17821782   
    17831783    offset=ii_begin
    1784     IF (is_north_pole) Offset=nbp_lon
     1784    IF (is_north_pole_dyn) Offset=nbp_lon
    17851785   
    17861786   
     
    17921792   
    17931793   
    1794     IF (is_north_pole) THEN
     1794    IF (is_north_pole_dyn) THEN
    17951795      DO i=1,dimsize
    17961796        DO ij=1,nbp_lon
     
    18001800    ENDIF
    18011801   
    1802     IF (is_south_pole) THEN
     1802    IF (is_south_pole_dyn) THEN
    18031803      DO i=1,dimsize
    18041804        DO ij=nbp_lon*(jj_nb-1)+1,nbp_lon*jj_nb
     
    18241824
    18251825    offset=ii_begin
    1826     IF (is_north_pole) offset=nbp_lon
     1826    IF (is_north_pole_dyn) offset=nbp_lon
    18271827
    18281828    DO i=1,dimsize
     
    18321832    ENDDO
    18331833
    1834     IF (is_north_pole) THEN
     1834    IF (is_north_pole_dyn) THEN
    18351835      DO i=1,dimsize
    18361836        VarOut(1,i)=VarIn(1,i)
     
    18541854
    18551855    offset=ii_begin
    1856     IF (is_north_pole) offset=nbp_lon
     1856    IF (is_north_pole_dyn) offset=nbp_lon
    18571857
    18581858    DO i=1,dimsize
     
    18621862    ENDDO
    18631863
    1864     IF (is_north_pole) THEN
     1864    IF (is_north_pole_dyn) THEN
    18651865      DO i=1,dimsize
    18661866         VarOut(1,i)=VarIn(1,i)
     
    18831883
    18841884    offset=ii_begin
    1885     IF (is_north_pole) offset=nbp_lon
     1885    IF (is_north_pole_dyn) offset=nbp_lon
    18861886
    18871887    DO i=1,dimsize
     
    18911891    ENDDO
    18921892
    1893     IF (is_north_pole) THEN
     1893    IF (is_north_pole_dyn) THEN
    18941894      DO i=1,dimsize
    18951895        VarOut(1,i)=VarIn(1,i)
  • trunk/LMDZ.GENERIC/libf/phy_common/mod_phys_lmdz_omp_data.F90

    r1543 r1682  
    11!
    2 !$Id: mod_phys_lmdz_omp_data.F90 2326 2015-07-10 12:24:29Z emillour $
     2!$Id: mod_phys_lmdz_omp_data.F90 2429 2016-01-27 12:43:09Z fairhead $
    33!
    44MODULE mod_phys_lmdz_omp_data
     
    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
     11  LOGICAL,SAVE :: is_north_pole_phy, is_south_pole_phy
    1012 
    1113  INTEGER,SAVE,DIMENSION(:),ALLOCATABLE :: klon_omp_para_nb
     
    1618  INTEGER,SAVE :: klon_omp_begin
    1719  INTEGER,SAVE :: klon_omp_end
    18 !$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)
     21!$OMP  THREADPRIVATE(is_north_pole_phy, is_south_pole_phy)
    1922
    2023CONTAINS
    2124 
    2225  SUBROUTINE Init_phys_lmdz_omp_data(klon_mpi)
    23     USE dimphy
     26    USE dimphy
     27    USE mod_phys_lmdz_mpi_data, ONLY : is_north_pole_dyn, is_south_pole_dyn
    2428    IMPLICIT NONE
    2529    INTEGER, INTENT(in) :: klon_mpi
     
    4347        omp_size=OMP_GET_NUM_THREADS()
    4448!$OMP END MASTER
     49!$OMP BARRIER
    4550        omp_rank=OMP_GET_THREAD_NUM()   
    4651#else   
     
    5661   ELSE
    5762     abort_message = 'ANORMAL : OMP_MASTER /= 0'
    58      CALL abort_gcm (modname,abort_message,1)
     63     CALL abort_physic (modname,abort_message,1)
    5964   ENDIF
    6065!$OMP END MASTER
    61 
     66   is_omp_master=is_omp_root
    6267
    6368!$OMP MASTER
     69
    6470    ALLOCATE(klon_omp_para_nb(0:omp_size-1))
    6571    ALLOCATE(klon_omp_para_begin(0:omp_size-1))
     
    8086!$OMP END MASTER
    8187!$OMP BARRIER
     88
     89   if ((is_north_pole_dyn) .AND. (omp_rank == 0 )) then
     90      is_north_pole_phy = .TRUE.
     91    else
     92      is_north_pole_phy = .FALSE.
     93    endif
     94    if ((is_south_pole_dyn) .AND. (omp_rank == omp_size-1)) then
     95      is_south_pole_phy = .TRUE.
     96    else
     97      is_south_pole_phy = .FALSE.
     98    endif
    8299   
    83100    klon_omp=klon_omp_para_nb(omp_rank)
     
    90107
    91108  SUBROUTINE Print_module_data
     109  USE print_control_mod, ONLY: lunout
    92110  IMPLICIT NONE
    93   INCLUDE "iniprint.h"
    94111
    95112!$OMP CRITICAL 
  • trunk/LMDZ.GENERIC/libf/phy_common/physics_distribution_mod.F90

    r1543 r1682  
    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
    1416  IMPLICIT NONE
    1517    INTEGER,INTENT(IN) :: grid_type
     
    2426    CALL init_grid_phy_lmdz(grid_type,nvertex, nbp_lon,nbp_lat,nbp_lev)
    2527    CALL init_phys_lmdz_para(nbp,nbp_lon, nbp_lat, communicator)
     28!$OMP PARALLEL
     29    CALL init_dimphy(klon_omp,nbp_lev)
     30!$OMP END PARALLEL
    2631
    2732  END SUBROUTINE init_physics_distribution 
  • trunk/LMDZ.GENERIC/libf/phy_common/print_control_mod.F90

    r1673 r1682  
    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
  • trunk/LMDZ.GENERIC/libf/phystd/inifis_mod.F90

    r1677 r1682  
    99             prad,pg,pr,pcpp)
    1010
     11  use init_print_control_mod, only: init_print_control
    1112  use radinc_h, only: ini_radinc_h, naerkind
    1213  use radcommon_h, only: ini_radcommon_h
     
    7677  REAL SSUM
    7778 
     79  ! Initialize flags lunout, prt_level, debug (in print_control_mod)
     80  CALL init_print_control
     81
    7882  ! initialize constants in comcstfi_mod
    7983  rad=prad
  • trunk/LMDZ.GENERIC/libf/phystd/ocean_slab_mod.F90

    r1397 r1682  
    9494      IF (error /= 0) THEN
    9595         abort_message='Pb allocation tmp_tslab'
    96          CALL abort_gcm(modname,abort_message,1)
     96         CALL abort_physic(modname,abort_message,1)
    9797      ENDIF
    9898      tmp_tslab(:,:) = tslab_rst(:,:)
     
    100100      IF (error /= 0) THEN
    101101         abort_message='Pb allocation tmp_tslab_loc'
    102          CALL abort_gcm(modname,abort_message,1)
     102         CALL abort_physic(modname,abort_message,1)
    103103      ENDIF
    104104      tmp_tslab_loc(:,:) = tslab_rst(:,:)
     
    107107    IF (error /= 0) THEN
    108108       abort_message='Pb allocation tmp_seaice'
    109        CALL abort_gcm(modname,abort_message,1)
     109       CALL abort_physic(modname,abort_message,1)
    110110    ENDIF
    111111    tmp_seaice(:) = seaice_rst(:)
     
    114114    IF (error /= 0) THEN
    115115       abort_message='Pb allocation tmp_pctsrf_slab'
    116        CALL abort_gcm(modname,abort_message,1)
     116       CALL abort_physic(modname,abort_message,1)
    117117    ENDIF
    118118    tmp_pctsrf_slab(:) = pctsrf_rst(:)
     
    122122    IF (error /= 0) THEN
    123123       abort_message='Pb allocation tmp_radsol'
    124        CALL abort_gcm(modname,abort_message,1)
     124       CALL abort_physic(modname,abort_message,1)
    125125    ENDIF
    126126
     
    128128    IF (error /= 0) THEN
    129129       abort_message='Pb allocation tmp_flux_o'
    130        CALL abort_gcm(modname,abort_message,1)
     130       CALL abort_physic(modname,abort_message,1)
    131131    ENDIF
    132132   
     
    134134    IF (error /= 0) THEN
    135135       abort_message='Pb allocation tmp_flux_g'
    136        CALL abort_gcm(modname,abort_message,1)
     136       CALL abort_physic(modname,abort_message,1)
    137137    ENDIF
    138138
     
    141141    IF (error /= 0) THEN
    142142       abort_message='Pb allocation slab_bils'
    143        CALL abort_gcm(modname,abort_message,1)
     143       CALL abort_physic(modname,abort_message,1)
    144144    ENDIF
    145145    slab_bils(:) = 0.0   
     
    148148    IF (error /= 0) THEN
    149149       abort_message='Pb allocation dt_hdiff'
    150        CALL abort_gcm(modname,abort_message,1)
     150       CALL abort_physic(modname,abort_message,1)
    151151    ENDIF
    152152    dt_hdiff = 0.0   
     
    155155    IF (error /= 0) THEN
    156156       abort_message='Pb allocation dt_hdiff'
    157        CALL abort_gcm(modname,abort_message,1)
     157       CALL abort_physic(modname,abort_message,1)
    158158    ENDIF
    159159    dt_ekman = 0.0   
     
    163163    IF (error /= 0) THEN
    164164       abort_message='Pb allocation lmt_bils'
    165        CALL abort_gcm(modname,abort_message,1)
     165       CALL abort_physic(modname,abort_message,1)
    166166    ENDIF
    167167    lmt_bils(:) = 0.0
     
    170170    IF (error /= 0) THEN
    171171       abort_message='Pb allocation slabh'
    172        CALL abort_gcm(modname,abort_message,1)
     172       CALL abort_physic(modname,abort_message,1)
    173173    ENDIF
    174174    slabh(1)=50.
  • trunk/LMDZ.GENERIC/libf/phystd/physiq_mod.F90

    r1669 r1682  
    4848      use callkeys_mod
    4949      use vertical_layers_mod, only: presnivs, pseudoalt
     50      use mod_phys_lmdz_omp_data, ONLY: is_omp_master
    5051#ifdef CPP_XIOS     
    5152      use xios_output_mod, only: initialize_xios_output, &
    5253                                 update_xios_timestep, &
    5354                                 send_xios_field
     55      use wxios, only: wxios_context_init, xios_context_finalize
    5456#endif
    5557      implicit none
     
    529531         endif
    530532
     533#ifdef CPP_XIOS
     534        ! Initialize XIOS context
     535        write(*,*) "physiq: call wxios_context_init"
     536        CALL wxios_context_init
     537#endif
    531538
    532539!        Read 'startfi.nc' file.
     
    735742                                     presnivs,pseudoalt)
    736743#endif
     744         write(*,*) "physiq: end of firstcall"
    737745      endif ! end of 'firstcall'
    738746
     
    18931901         end if
    18941902
    1895          
    1896       endif ! end of 'lastcall'
     1903    endif ! end of 'lastcall'
    18971904
    18981905
     
    21812188      CALL send_xios_field("u",zu)
    21822189      CALL send_xios_field("v",zv)
    2183      
     2190
     2191      if (lastcall.and.is_omp_master) then
     2192        write(*,*) "physiq: call xios_context_finalize"
     2193        call xios_context_finalize
     2194      endif
    21842195#endif
    21852196
  • trunk/LMDZ.GENERIC/libf/phystd/xios_output_mod.F90

    r1626 r1682  
    2626                                mpi_size, mpi_rank, klon_mpi, &
    2727                                is_sequential, is_south_pole_dyn
    28   USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, klon_glo
     28  USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, klon_glo, grid_type, unstructured
    2929  USE print_control_mod, ONLY: lunout, prt_level
    3030  USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat
    3131  USE regular_lonlat_mod, ONLY: lon_reg, lat_reg
    3232  USE nrtype, ONLY: pi
    33   USE wxios
     33#ifdef CPP_XIOS
     34  USE xios
     35#endif
     36  USE wxios, ONLY: wxios_domain_param, wxios_domain_param_unstructured, wxios_closedef
    3437  IMPLICIT NONE
    3538 
     
    6063    ! 2. Declare horizontal domain
    6164    ! Set values for the mask:
    62     IF (mpi_rank == 0) THEN
    63         data_ibegin = 0
    64     ELSE
    65         data_ibegin = ii_begin - 1
    66     END IF
    67 
    68     IF (mpi_rank == mpi_size-1) THEN
    69         data_iend = nbp_lon
    70     ELSE
    71         data_iend = ii_end + 1
    72     END IF
    73 
    74     if (prt_level>=10) then
    75       write(lunout,*) "initialize_xios_output: mpirank=",mpi_rank," iibegin=",ii_begin , " ii_end=",ii_end," jjbegin=",jj_begin," jj_nb=",jj_nb," jj_end=",jj_end
    76       write(lunout,*) "initialize_xios_output: mpirank=",mpi_rank," nbp_lon=",nbp_lon," nbp_lat=",nbp_lat
    77       write(lunout,*) "initialize_xios_output: mpirank=",mpi_rank," data_ibegin=",data_ibegin," data_iend=",data_iend
    78       write(lunout,*) "initialize_xios_output: mpirank=",mpi_rank," data_ibegin=",data_ibegin," data_iend=",data_iend
    79       write(lunout,*) "initialize_xios_output: mpirank=",mpi_rank," is_south_pole=",is_south_pole_dyn
    80     endif
    81 
     65!    IF (mpi_rank == 0) THEN
     66!        data_ibegin = 0
     67!    ELSE
     68!        data_ibegin = ii_begin - 1
     69!    END IF
     70
     71!    IF (mpi_rank == mpi_size-1) THEN
     72!        data_iend = nbp_lon
     73!    ELSE
     74!        data_iend = ii_end + 1
     75!    END IF
     76
     77!    if (prt_level>=10) then
     78!      write(lunout,*) "initialize_xios_output: mpirank=",mpi_rank," iibegin=",ii_begin , " ii_end=",ii_end," jjbegin=",jj_begin," jj_nb=",jj_nb," jj_end=",jj_end
     79!      write(lunout,*) "initialize_xios_output: mpirank=",mpi_rank," nbp_lon=",nbp_lon," nbp_lat=",nbp_lat
     80!      write(lunout,*) "initialize_xios_output: mpirank=",mpi_rank," data_ibegin=",data_ibegin," data_iend=",data_iend
     81!      write(lunout,*) "initialize_xios_output: mpirank=",mpi_rank," data_ibegin=",data_ibegin," data_iend=",data_iend
     82!      write(lunout,*) "initialize_xios_output: mpirank=",mpi_rank," is_south_pole=",is_south_pole_dyn
     83!    endif
     84
     85!$OMP END MASTER
     86!$OMP BARRIER
    8287    ! Initialize the XIOS domain coreesponding to this process:
    8388    if (prt_level>=10) write(lunout,*) "initialize_xios_output: call wxios_domain_param"
    84     CALL wxios_domain_param("dom_glo", is_sequential, nbp_lon, jj_nb, nbp_lon, nbp_lat, &
    85                             1, nbp_lon, ii_begin, ii_end, jj_begin, jj_end,             &
    86                             klon_mpi+2*(nbp_lon-1), data_ibegin, data_iend,             &
    87                             lat_reg*(180./pi), lon_reg*(180./pi),                       &
    88                             is_south_pole_dyn,mpi_rank)
    89 
     89!    CALL wxios_domain_param("dom_glo", is_sequential, nbp_lon, jj_nb, nbp_lon, nbp_lat, &
     90!                            1, nbp_lon, ii_begin, ii_end, jj_begin, jj_end,             &
     91!                            klon_mpi+2*(nbp_lon-1), data_ibegin, data_iend,             &
     92!                            lat_reg*(180./pi), lon_reg*(180./pi),                       &
     93!                            is_south_pole_dyn,mpi_rank)
     94
     95    IF (grid_type==unstructured) THEN
     96      CALL wxios_domain_param_unstructured("dom_glo")
     97    ELSE
     98      CALL wxios_domain_param("dom_glo")
     99    ENDIF
     100
     101!$OMP MASTER
    90102    ! 3. Declare calendar and time step
    91103    if (prt_level>=10) write(lunout,*) "initialize_xios_output: build calendar"
Note: See TracChangeset for help on using the changeset viewer.