Changeset 3751 for LMDZ6


Ignore:
Timestamp:
Jul 8, 2020, 7:49:06 PM (4 years ago)
Author:
adurocher
Message:

Check if field is active before omp_gather (dynamic check)

At each timestep and for every field xios_field_is_active( <field>, at_current_timestep_arg=.true.) is called

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Optimisation_LMDZ/libf/phylmd/iophy.F90

    r3488 r3751  
    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    IF (ok_all_xml) THEN
     1039      !$omp barrier
     1040      !$omp master
     1041      is_active = xios_field_is_active(var%name, at_current_timestep_arg=.true.)
     1042      !$omp end master
     1043      !$omp barrier
     1044      IF(.not. is_active) RETURN
     1045    ENDIF
    10371046
    10381047    !Et sinon on.... écrit
     
    11761185  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, grid_type, regular_lonlat, unstructured
    11771186#ifdef CPP_XIOS
    1178   USE xios, ONLY: xios_send_field
     1187  USE xios, ONLY: xios_send_field, xios_field_is_active
    11791188#endif
    11801189  USE print_control_mod, ONLY: prt_level,lunout
     
    11951204  INTEGER, ALLOCATABLE, DIMENSION(:) :: index3d
    11961205  REAL,ALLOCATABLE, DIMENSION(:,:) :: fieldok
     1206  logical, save :: is_active = .true.
    11971207
    11981208  IF (check_dim .AND. is_master) WRITE(lunout,*)'histwrite3d_phy for ', trim(var%name)
     
    12221232      CALL bcast_omp(swaerofree_diag)
    12231233  ELSE
     1234    IF (ok_all_xml) THEN
     1235      !$omp barrier
     1236      !$omp master
     1237      is_active = xios_field_is_active(var%name, at_current_timestep_arg=.true.)
     1238      !$omp end master
     1239      !$omp barrier
     1240      IF(.not. is_active) RETURN
     1241    ENDIF
     1242
    12241243    !Et sinon on.... écrit
    1225 
    12261244    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)
    12271245
Note: See TracChangeset for help on using the changeset viewer.