Ignore:
Timestamp:
Mar 17, 2022, 11:51:36 AM (2 years ago)
Author:
Laurent Fairhead
Message:

Inclusion of some corrections and optimisations for XIOS done by
Arnaud Durocher during his TGCC mission.
Included here are r3703, r3704, r3750, r3751, r3752 from his
LMDZ6/branches/Optimisation_LMDZ branch

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/iophy.F90

    r4046 r4103  
    975975  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, grid_type, unstructured, regular_lonlat
    976976#ifdef CPP_XIOS
    977   USE xios, ONLY: xios_send_field
     977  USE xios, ONLY: xios_send_field, xios_field_is_active
    978978#endif
    979979  USE print_control_mod, ONLY: lunout, prt_level
     
    996996  INTEGER :: ip
    997997  REAL, ALLOCATABLE, DIMENSION(:) :: fieldok
     998  logical, save :: is_active = .true.
    998999
    9991000  IF (check_dim .AND. is_master) WRITE(lunout,*)'histwrite2d_phy for ',trim(var%name)
     
    10351036
    10361037  ELSE
     1038#ifdef CPP_XIOS
     1039    IF (ok_all_xml) THEN
     1040      !$omp barrier
     1041      !$omp master
     1042      is_active = xios_field_is_active(var%name, at_current_timestep_arg=.false.)
     1043      !$omp end master
     1044      !$omp barrier
     1045      IF(.not. is_active) RETURN
     1046    ENDIF
     1047#endif
    10371048
    10381049    !Et sinon on.... écrit
     
    11761187  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, grid_type, regular_lonlat, unstructured
    11771188#ifdef CPP_XIOS
    1178   USE xios, ONLY: xios_send_field
     1189  USE xios, ONLY: xios_send_field, xios_field_is_active
    11791190#endif
    11801191  USE print_control_mod, ONLY: prt_level,lunout
     
    11951206  INTEGER, ALLOCATABLE, DIMENSION(:) :: index3d
    11961207  REAL,ALLOCATABLE, DIMENSION(:,:) :: fieldok
     1208  logical, save :: is_active = .true.
    11971209
    11981210  IF (check_dim .AND. is_master) WRITE(lunout,*)'histwrite3d_phy for ', trim(var%name)
     
    12221234      CALL bcast_omp(swaerofree_diag)
    12231235  ELSE
     1236#ifdef CPP_XIOS
     1237    IF (ok_all_xml) THEN
     1238      !$omp barrier
     1239      !$omp master
     1240      is_active = xios_field_is_active(var%name, at_current_timestep_arg=.false.)
     1241      !$omp end master
     1242      !$omp barrier
     1243      IF(.not. is_active) RETURN
     1244    ENDIF
     1245#endif
     1246
    12241247    !Et sinon on.... écrit
    1225 
    12261248    IF (SIZE(field,1)/=klon .AND. SIZE(field,1)/=klev .AND. SIZE(field,1)/=klev+1) CALL abort_physic('iophy::histwrite3d_phy','Field first DIMENSION not equal to klon/klev',1)
    12271249
Note: See TracChangeset for help on using the changeset viewer.