Changeset 3754


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

Fix conditional compilation to compile without XIOS

Location:
LMDZ6/branches/Optimisation_LMDZ/libf
Files:
2 added
6 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Optimisation_LMDZ/libf/misc/wxios.F90

    r3465 r3754  
    673673     END SUBROUTINE wxios_close
    674674END MODULE wxios
     675#else
     676MODULE wxios
     677    REAL :: missing_val = 0
     678contains
     679    SUBROUTINE wxios_set_context()
     680    END SUBROUTINE wxios_set_context
     681    SUBROUTINE wxios_closedef()
     682    END SUBROUTINE wxios_closedef
     683END MODULE wxios   
    675684#endif
  • LMDZ6/branches/Optimisation_LMDZ/libf/phylmd/iophy_xios.f90

    r3753 r3754  
    22! ok_all_xml must be true
    33MODULE iophy_xios
    4   use iophy, only: npstn, nptabij, check_dim
     4  use iophy, only: check_dim
    55  implicit none
    66
     
    2121    USE mod_phys_lmdz_para, ONLY: is_master
    2222    USE phys_output_var_mod, ONLY: ctrl_out
    23     USE xios, ONLY: xios_field_is_active
     23    USE xios_interface, ONLY: xios_field_is_active
    2424    USE print_control_mod, ONLY: lunout
    2525    IMPLICIT NONE
     
    4747    USE phys_output_var_mod, ONLY: ctrl_out
    4848    USE print_control_mod, ONLY: lunout
    49     USE xios, ONLY: xios_field_is_active
     49    USE xios_interface, ONLY: xios_field_is_active
    5050    IMPLICIT NONE
    5151    INCLUDE 'clesphys.h'
     
    7474                                  jj_nb, klon_mpi, is_master
    7575    USE mod_grid_phy_lmdz, ONLY: nbp_lon, grid_type, unstructured, regular_lonlat
    76     USE xios, ONLY: xios_send_field
     76    USE xios_interface, ONLY: xios_send_field
    7777    USE print_control_mod, ONLY: lunout
    7878
     
    120120    USE mod_phys_lmdz_para, ONLY: gather_omp, grid1Dto2D_mpi, &
    121121                                  jj_nb, klon_mpi, is_master
    122     USE xios, ONLY: xios_send_field
     122    USE xios_interface, ONLY: xios_send_field
    123123    USE mod_grid_phy_lmdz, ONLY: nbp_lon, grid_type, regular_lonlat, unstructured
    124124    USE print_control_mod, ONLY: lunout
     
    167167
    168168  SUBROUTINE histwrite0d_xios(field_name, field)
    169     USE xios, ONLY: xios_send_field
     169    USE xios_interface, ONLY: xios_send_field
    170170    USE mod_phys_lmdz_para, ONLY: is_master
    171171    USE print_control_mod, ONLY: lunout
  • LMDZ6/branches/Optimisation_LMDZ/libf/phylmd/phys_output_write_mod.F90

    r3630 r3754  
    460460 !      iinitend = 1
    461461 !   ENDIF
     462   if( ok_all_xml ) call abort_physic("phys_output_write", "Support of this IO backend with ok_all_xml=.true. is deprecated : use phys_output_write_xios instead", 1)
    462463
    463464#ifdef CPP_XIOS
  • LMDZ6/branches/Optimisation_LMDZ/libf/phylmd/phys_output_write_xios_mod.f90

    r3753 r3754  
    326326    USE print_control_mod, ONLY: prt_level, lunout
    327327
    328     USE xios
     328    USE xios_interface, ONLY : CPP_XIOS_defined, xios_fieldgroup, xios_field, xios_get_handle, xios_add_child, xios_set_attr, xios_update_calendar
    329329    USE wxios, ONLY: wxios_closedef, missing_val, wxios_set_context
    330330    USE vertical_layers_mod, ONLY: presnivs
     
    382382    REAL, DIMENSION(klon)      :: zrho, zt
    383383
     384    if( .not. CPP_XIOS_defined ) call abort_physic("phys_output_write_xios", "This io backend can only be used when LMDZ is compiled with XIOS support",1 )
    384385    if( .not. ok_all_xml ) call abort_physic("phys_output_write_xios", "This io backend only supports ok_all_xml = .true.", 1)
    385386
  • LMDZ6/branches/Optimisation_LMDZ/libf/phylmd/phys_output_write_xios_preprocess.F90

    r3753 r3754  
    1 #ifndef CPP_XIOS
    2 #error "CPP_XIOS must be defined to compile this file"
    3 #endif
    4 #ifndef CPP_IOIPSL_NO_OUTPUT
    5 #error "CPP_IOIPSL_NO_OUTPUT is not mandatory to compile this file"
    6 #endif
    7 
    81MODULE phys_output_write_xios_preprocess
    92
  • LMDZ6/branches/Optimisation_LMDZ/libf/phylmd/physiq_mod.F90

    r3753 r3754  
    223223#endif
    224224
    225     USE phys_output_write_xios_mod
     225    USE phys_output_write_interface_mod, only : phys_output_write, phys_output_write_xios
    226226    USE fonte_neige_mod, ONLY  : fonte_neige_get_vars
    227227    USE phys_output_mod
     
    16941694        ENDIF
    16951695
    1696        CALL phys_output_write_xios(itap, pdtphys, paprs, pphis,                    &
     1696      if( ok_all_xml ) then
     1697         CALL phys_output_write_xios(itap, pdtphys, paprs, pphis,                    &
    16971698                              pplay, lmax_th, aerosol_couple,                 &
    16981699                              ok_ade, ok_aie, ok_volcan, ivap, iliq, isol, ok_sync,&
     
    17001701                              ptconvth, d_u, d_t, qx, d_qx, zmasse,           &
    17011702                              flag_aerosol, flag_aerosol_strat, ok_cdnc)
     1703      else
     1704         CALL phys_output_write(itap, pdtphys, paprs, pphis,                    &
     1705                              pplay, lmax_th, aerosol_couple,                 &
     1706                              ok_ade, ok_aie, ok_volcan, ivap, iliq, isol, ok_sync,&
     1707                              ptconv, read_climoz, clevSTD,                   &
     1708                              ptconvth, d_u, d_t, qx, d_qx, zmasse,           &
     1709                              flag_aerosol, flag_aerosol_strat, ok_cdnc)
     1710      endif
    17021711
    17031712#ifdef CPP_XIOS
     
    51115120       flag_aerosol, flag_aerosol_strat, ok_cdnc)
    51125121#else
    5113     CALL phys_output_write_xios(itap, pdtphys, paprs, pphis,  &
    5114          pplay, lmax_th, aerosol_couple,                 &
    5115          ok_ade, ok_aie, ok_volcan, ivap, iliq, isol,    &
    5116          ok_sync, ptconv, read_climoz, clevSTD,          &
    5117          ptconvth, d_u, d_t, qx, d_qx, zmasse,           &
    5118          flag_aerosol, flag_aerosol_strat, ok_cdnc)
     5122   if( ok_all_xml ) then
     5123      CALL phys_output_write_xios(itap, pdtphys, paprs, pphis,                    &
     5124                             pplay, lmax_th, aerosol_couple,                 &
     5125                             ok_ade, ok_aie, ok_volcan, ivap, iliq, isol, ok_sync,&
     5126                             ptconv, read_climoz, clevSTD,                   &
     5127                             ptconvth, d_u, d_t, qx, d_qx, zmasse,           &
     5128                             flag_aerosol, flag_aerosol_strat, ok_cdnc)
     5129   else
     5130      CALL phys_output_write(itap, pdtphys, paprs, pphis,                    &
     5131                           pplay, lmax_th, aerosol_couple,                 &
     5132                           ok_ade, ok_aie, ok_volcan, ivap, iliq, isol, ok_sync,&
     5133                           ptconv, read_climoz, clevSTD,                   &
     5134                           ptconvth, d_u, d_t, qx, d_qx, zmasse,           &
     5135                           flag_aerosol, flag_aerosol_strat, ok_cdnc)
     5136   endif
    51195137#endif
    51205138
Note: See TracChangeset for help on using the changeset viewer.