Ignore:
Timestamp:
Jul 10, 2023, 1:40:39 AM (18 months ago)
Author:
yann meurdesoif
Message:

Suppress usage of preprocessing key CPP_XIOS.
Wrapper file is used to suppress XIOS symbol when xios is not linked and not used (-io ioipsl)
The CPP_XIOS key is replaced in model by "using_xios" boolean variable to switch between IOIPSL or XIOS output.

YM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/Dust/phys_output_write_spl_mod.F90

    r4593 r4619  
    389389    USE iophy, ONLY: set_itau_iophy, histwrite_phy
    390390    USE netcdf, ONLY: nf90_fill_real
    391 
    392 #ifdef CPP_XIOS
    393391    ! ug Pour les sorties XIOS
    394     USE xios, ONLY: xios_update_calendar
    395     USE wxios, ONLY: wxios_closedef, missing_val
    396 #endif
     392    USE lmdz_xios, ONLY: xios_update_calendar, using_xios
     393    USE wxios, ONLY: wxios_closedef, missing_val_xios => missing_val
    397394    USE phys_cal_mod, ONLY : mth_len
    398395
     
    438435    INTEGER, DIMENSION(iim*jjmp1*klev) :: ndex3d
    439436    REAL, PARAMETER :: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2
    440 !   REAL, PARAMETER :: missing_val=nf90_fill_real
    441 #ifndef CPP_XIOS
    442437    REAL :: missing_val
    443 #endif
    444438    REAL, PARAMETER :: un_jour=86400.
     439
     440    IF (using_xios) THEN
     441      missing_val=missing_val_xios
     442    ELSE
     443      missing_val=nf90_fill_real
     444    ENDIF
    445445
    446446    ! On calcul le nouveau tau:
     
    460460    ! ug la boucle qui suit ne sert qu'une fois, pour l'initialisation, sinon il n'y a toujours qu'un seul passage:
    461461    DO iinit=1, iinitend
    462 #ifdef CPP_XIOS
    463        !$OMP MASTER
    464        IF (vars_defined) THEN
    465           IF (prt_level >= 10) THEN
    466              write(lunout,*)"phys_output_write: call xios_update_calendar, itau_w=",itau_w
    467           ENDIF
    468 !          CALL xios_update_calendar(itau_w)
    469           CALL xios_update_calendar(itap)
    470        ENDIF
    471        !$OMP END MASTER
    472        !$OMP BARRIER
    473 #endif
     462       IF (using_xios) THEN
     463         !$OMP MASTER
     464         IF (vars_defined) THEN
     465            IF (prt_level >= 10) THEN
     466               write(lunout,*)"phys_output_write: call xios_update_calendar, itau_w=",itau_w
     467            ENDIF
     468!           CALL xios_update_calendar(itau_w)
     469            CALL xios_update_calendar(itap)
     470         ENDIF
     471         !$OMP END MASTER
     472         !$OMP BARRIER
     473       ENDIF !using_xios
     474
    474475       ! On procède à l'écriture ou à la définition des nombreuses variables:
    475476!!! Champs 1D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    828829
    829830#ifdef CPP_IOIPSL
    830 #ifndef CPP_XIOS
    831   IF (.NOT.ok_all_xml) THEN
    832        ! ATTENTION, LES ANCIENS HISTWRITE ONT ETES CONSERVES EN ATTENDANT MIEUX:
    833        ! Champs interpolles sur des niveaux de pression
    834        missing_val=missing_val_nf90
    835        DO iff=1, nfiles
    836           ll=0
    837           DO k=1, nlevSTD
    838              bb2=clevSTD(k)
    839              IF (bb2.EQ."850".OR.bb2.EQ."700".OR. &
    840                   bb2.EQ."500".OR.bb2.EQ."200".OR. &
    841                   bb2.EQ."100".OR. &
    842                   bb2.EQ."50".OR.bb2.EQ."10") THEN
    843 
    844                 ! a refaire correctement !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    845                 ll=ll+1
    846                 CALL histwrite_phy(o_uSTDlevs(ll),uwriteSTD(:,k,iff), iff)
    847                 CALL histwrite_phy(o_vSTDlevs(ll),vwriteSTD(:,k,iff), iff)
    848                 CALL histwrite_phy(o_wSTDlevs(ll),wwriteSTD(:,k,iff), iff)
    849                 CALL histwrite_phy(o_zSTDlevs(ll),phiwriteSTD(:,k,iff), iff)
    850                 CALL histwrite_phy(o_qSTDlevs(ll),qwriteSTD(:,k,iff), iff)
    851                 CALL histwrite_phy(o_tSTDlevs(ll),twriteSTD(:,k,iff), iff)
    852 
    853              ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR.
    854           ENDDO
    855        ENDDO
    856   ENDIF
     831  IF (.NOT. using_xios) THEN
     832    IF (.NOT.ok_all_xml) THEN
     833         ! ATTENTION, LES ANCIENS HISTWRITE ONT ETES CONSERVES EN ATTENDANT MIEUX:
     834         ! Champs interpolles sur des niveaux de pression
     835         DO iff=1, nfiles
     836           ll=0
     837            DO k=1, nlevSTD
     838               bb2=clevSTD(k)
     839               IF (bb2.EQ."850".OR.bb2.EQ."700".OR. &
     840                    bb2.EQ."500".OR.bb2.EQ."200".OR. &
     841                    bb2.EQ."100".OR. &
     842                    bb2.EQ."50".OR.bb2.EQ."10") THEN
     843
     844                  ! a refaire correctement !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     845                  ll=ll+1
     846                  CALL histwrite_phy(o_uSTDlevs(ll),uwriteSTD(:,k,iff), iff)
     847                  CALL histwrite_phy(o_vSTDlevs(ll),vwriteSTD(:,k,iff), iff)
     848                  CALL histwrite_phy(o_wSTDlevs(ll),wwriteSTD(:,k,iff), iff)
     849                  CALL histwrite_phy(o_zSTDlevs(ll),phiwriteSTD(:,k,iff), iff)
     850                  CALL histwrite_phy(o_qSTDlevs(ll),qwriteSTD(:,k,iff), iff)
     851                  CALL histwrite_phy(o_tSTDlevs(ll),twriteSTD(:,k,iff), iff)
     852
     853               ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR.
     854            ENDDO
     855         ENDDO
     856    ENDIF
     857  ENDIF !.NOT.using_xios
    857858#endif
    858 #endif
    859 
    860 #ifdef CPP_XIOS
    861   IF (ok_all_xml) THEN
    862 !XIOS  CALL xios_get_field_attr("u850",default_value=missing_val)
    863 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     859
     860  IF (using_xios) THEN
     861    IF (ok_all_xml) THEN
     862  !XIOS  CALL xios_get_field_attr("u850",default_value=missing_val)
     863  !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    864864          ll=0
    865865          DO k=1, nlevSTD
     
    878878             ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR.
    879879          ENDDO
    880   ENDIF
    881 #endif
     880    ENDIF
     881  ENDIF !using_xios
    882882       IF (vars_defined) THEN
    883883          DO i=1, klon
     
    14711471!!!!!!!!!!!! Sorties niveaux de pression NMC !!!!!!!!!!!!!!!!!!!!
    14721472#ifdef CPP_IOIPSL
    1473 #ifndef CPP_XIOS
    1474   IF (.NOT.ok_all_xml) THEN
    1475        ! ATTENTION, LES ANCIENS HISTWRITE ONT ETES CONSERVES EN ATTENDANT MIEUX:
    1476        ! Champs interpolles sur des niveaux de pression
    1477        missing_val=missing_val_nf90
     1473
     1474  IF (.NOT. using_xios) THEN
     1475    IF (.NOT.ok_all_xml) THEN
     1476         ! ATTENTION, LES ANCIENS HISTWRITE ONT ETES CONSERVES EN ATTENDANT MIEUX:
     1477         ! Champs interpolles sur des niveaux de pression
    14781478       DO iff=7, nfiles-1 !--here we deal with files 7,8 and 9
    14791479
     
    15391539          CALL histwrite_phy(o_TxT,T2sumSTD(:,:,iff-6),iff)
    15401540       ENDDO !nfiles
     1541    ENDIF
    15411542  ENDIF
    15421543#endif
    1543 #endif
    1544 #ifdef CPP_XIOS
     1544
     1545IF (using_xios) THEN
    15451546  IF (ok_all_xml) THEN
    15461547!      DO iff=7, nfiles
     
    16071608          CALL histwrite_phy(o_TxT,T2STD(:,:))
    16081609!      ENDDO !nfiles
    1609   ENDIF
    1610 #endif
     1610    ENDIF
     1611  ENDIF !using_xios
    16111612!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    16121613           itr = 0
     
    16511652          ENDDO !  iff
    16521653#endif
    1653 #ifdef CPP_XIOS
    16541654          !On finalise l'initialisation:
    1655           CALL wxios_closedef()
    1656 #endif
     1655          IF (using_xios) CALL wxios_closedef()
    16571656
    16581657          !$OMP END MASTER
Note: See TracChangeset for help on using the changeset viewer.