Ignore:
Timestamp:
Mar 17, 2022, 11:51:36 AM (3 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

Location:
LMDZ6/trunk/libf/phylmd
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/cosp/dsd.F90

    r2428 r4103  
    5757  integer, intent(in) :: nsizes
    5858  integer, intent(in) :: dtype
    59   real*8, intent(in)  :: Q,Re,Np,D(nsizes)
     59  real*8, intent(in)  :: Q,Re_,Np,D(nsizes)
    6060  real*8, intent(in)  :: rho_a,tk,dmin,dmax,rho_c,p1,p2,p3
    6161   
     
    7878  real*8 :: tmp1, tmp2
    7979  real*8 :: pi,rc,tc
     80  real*8 :: Re
    8081
    8182  integer k,lidx,uidx
     83
     84  Re = Re_
    8285
    8386  tc = tk - 273.15
  • LMDZ6/trunk/libf/phylmd/cosp/radar_simulator.F90

    r2428 r4103  
    9696  real*8, dimension(hp%nhclass,nprof,ngate), intent(in) :: hm_matrix
    9797  real*8, dimension(hp%nhclass,nprof,ngate), intent(inout) :: re_matrix
    98   real*8, dimension(hp%nhclass,nprof,ngate), intent(in)    :: Np_matrix
     98  real*8, dimension(hp%nhclass,nprof,ngate), intent(inout)    :: Np_matrix
    9999
    100100! ----- OUTPUTS -----
  • 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
  • LMDZ6/trunk/libf/phylmd/mo_simple_plumes.F90

    r3531 r4103  
    280280
    281281    IF ((iweek > ntimes) .OR. (iweek < 1) .OR. (iyear > nyears) .OR. (iyear < 1)) THEN
    282       CALL abort_physic('set_time_weight','Time out of bounds')
     282      CALL abort_physic('set_time_weight','Time out of bounds',1)
    283283    ENDIF
    284284
  • LMDZ6/trunk/libf/phylmd/o3_chem_m.F90

    r2346 r4103  
    8585    ! Heterogeneous chemistry is only during daytime:
    8686    call orbite(real(julien), earth_long, trash1)
    87     call zenang(earth_long, gmtime, pdtphys, rlat, rlon, pmu0, trash2)
     87    call zenang(earth_long, gmtime, 0., pdtphys, rlat, rlon, pmu0, trash2)
    8888    forall (k = 1: nbp_lev)
    8989       where (pmu0 <= cos(87. / 180. * pi)) b(:, k) = 0.
  • LMDZ6/trunk/libf/phylmd/readaerosol_mod.F90

    r3440 r4103  
    1010!$OMP THREADPRIVATE(nbp_lat_src) 
    1111  REAL, ALLOCATABLE, SAVE    :: psurf_interp(:,:)
    12 !$OMP THREADPRIVATE(psurf_interp) 
    1312
    1413CONTAINS
     
    692691        CALL xios_send_field("load_"//TRIM(varname)//"_in",load_glo2D)
    693692        CALL xios_recv_field("load_"//TRIM(varname)//"_out",load_out_mpi)
    694         IF (first) THEN
     693        IF (.not. allocated(psurf_interp)) THEN
     694         ! psurf_interp is a shared array
    695695          ALLOCATE(psurf_interp(klon_mpi,12))
    696696          CALL xios_send_field("psurf_aerosol_in",psurf_glo2D)
  • LMDZ6/trunk/libf/phylmd/rrtm/abor1.intfb.h

    r1990 r4103  
    11INTERFACE
    22SUBROUTINE ABOR1(CDTEXT)
    3 CHARACTER(LEN=*) :: CDTEXT
     3CHARACTER(LEN=*), INTENT(IN) :: CDTEXT
    44END SUBROUTINE ABOR1
    55END INTERFACE
  • LMDZ6/trunk/libf/phylmd/rrtm/tpm_fft.F90

    r2010 r4103  
    77
    88TYPE FFT_TYPE
    9   REAL(KIND=JPRB)   ,POINTER :: TRIGS(:,:)
    10   INTEGER(KIND=JPIM),POINTER :: NFAX(:,:)
     9  REAL(KIND=JPRB)   ,ALLOCATABLE :: TRIGS(:,:)
     10  INTEGER(KIND=JPIM),ALLOCATABLE :: NFAX(:,:)
    1111END TYPE FFT_TYPE
    1212
Note: See TracChangeset for help on using the changeset viewer.