Changeset 4619


Ignore:
Timestamp:
Jul 10, 2023, 1:40:39 AM (10 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

Location:
LMDZ6/trunk/libf
Files:
1 added
60 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3d/abort_gcm.F

    r2100 r4619  
    1212      USE ioipsl_getincom
    1313#endif
    14 
    15 #ifdef CPP_XIOS
    16     ! ug Pour les sorties XIOS
     14 ! ug Pour les sorties XIOS
    1715      USE wxios
    18 #endif
    1916
    2017#include "iniprint.h"
     
    3431      write(lunout,*) 'in abort_gcm'
    3532
    36 #ifdef CPP_XIOS
    37     !Fermeture propre de XIOS
    38       CALL wxios_close()
    39 #endif
     33      IF (using_xios) THEN
     34!Fermeture propre de XIOS
     35        CALL wxios_close()
     36      ENDIF
    4037
    4138#ifdef CPP_IOIPSL
  • LMDZ6/trunk/libf/dyn3d/gcm.F90

    r4361 r4619  
    1414
    1515
    16 #ifdef CPP_XIOS
    17   ! ug Pour les sorties XIOS
     16! ug Pour les sorties XIOS
    1817  USE wxios
    19 #endif
    2018
    2119  USE filtreg_mod
     
    156154!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    157155
    158 #ifdef CPP_XIOS
    159   CALL wxios_init("LMDZ")
    160 #endif
     156  IF (using_xios) THEN
     157    CALL wxios_init("LMDZ")
     158  ENDIF
    161159
    162160
  • LMDZ6/trunk/libf/dyn3dmem/gcm.F90

    r4361 r4619  
    2828                       itau_dyn,itau_phy,day_ini,jD_ref,jH_ref,day_end, &
    2929                       dt,hour_ini,itaufin
    30 #ifdef CPP_XIOS
    3130  USE mod_xios_dyn3dmem, ONLY: xios_dyn3dmem_init
    32 #endif
    3331
    3432  IMPLICIT NONE
     
    457455
    458456! setting up DYN3D/XIOS inerface
    459 #ifdef CPP_XIOS
    460    if (ok_dyn_xios) then
    461      CALL xios_dyn3dmem_init(xios_cal_type, anref, moisref, jourref,heureref, an,   &
     457  if (ok_dyn_xios) then
     458      CALL xios_dyn3dmem_init(xios_cal_type, anref, moisref, jourref,heureref, an,   &
    462459          mois, jour, heure, zdtvr)
    463460  endif
    464 #endif
    465461
    466462  ! #endif of #ifdef CPP_IOIPSL
  • LMDZ6/trunk/libf/dyn3dmem/leapfrog_loc.F

    r4607 r4619  
    4242       USE temps_mod, ONLY: itaufin,jD_ref,jH_ref,day_ini,
    4343     &                        day_ref,start_time,dt
    44 #ifdef CPP_XIOS
    4544       USE mod_xios_dyn3dmem, ONLY : dyn3d_ctx_handle
    46        USE xios, ONLY: xios_update_calendar, xios_set_current_context
    47 #endif
     45       USE lmdz_xios, ONLY: xios_update_calendar,
     46     &                      xios_set_current_context,
     47     &                      using_xios
    4848       
    4949      IMPLICIT NONE
     
    15231523            CALL finalize_inca
    15241524!     switching back to LMDZDYN context
    1525 #ifdef CPP_XIOS
    15261525!$OMP MASTER
    15271526            IF (ok_dyn_xios) THEN
     
    15291528            ENDIF
    15301529!$OMP END MASTER
    1531 #endif
    15321530         ENDIF
    15331531#endif
     
    15821580                 CALL finalize_inca
    15831581!     switching back to LMDZDYN context
    1584 #ifdef CPP_XIOS
    15851582!$OMP MASTER
    15861583                 IF (ok_dyn_xios) THEN
     
    15881585                 ENDIF
    15891586!$OMP END MASTER
    1590 #endif
    15911587              ENDIF
    15921588#endif
     
    16611657#endif
    16621658             
    1663 #ifdef CPP_XIOS
    16641659              IF (ok_dyn_xios) THEN
    16651660c$OMP MASTER
     
    16701665     &                 ucov,teta,pk,phi,q,masse,ps,phis)
    16711666              ENDIF
    1672 #endif
    16731667             
    16741668          endif                 ! of if (leapf.or.(.not.leapf.and.(.not.forward)))
     
    17591753                    CALL finalize_inca
    17601754!     switching back to LMDZDYN context
    1761 #ifdef CPP_XIOS
    17621755!$OMP MASTER
    17631756                    IF (ok_dyn_xios) THEN
     
    17651758                    ENDIF
    17661759!$OMP END MASTER
    1767 #endif
    17681760                 ENDIF
    17691761
     
    18331825#endif
    18341826
    1835 #ifdef CPP_XIOS
    18361827              IF (ok_dyn_xios) THEN
    18371828c$OMP MASTER
     
    18421833     &                 ucov,teta,pk,phi,q,masse,ps,phis)
    18431834              ENDIF
    1844 #endif
    18451835             
    18461836           ENDIF                ! of IF(MOD(itau,iecri).EQ.0)
     
    18771867         CALL finalize_inca
    18781868!     switching back to LMDZDYN context
    1879 #ifdef CPP_XIOS
    18801869!$OMP MASTER
    18811870         IF (ok_dyn_xios) THEN
     
    18831872         ENDIF
    18841873!$OMP END MASTER
    1885 #endif
    18861874      ENDIF
    18871875
  • LMDZ6/trunk/libf/dyn3dmem/mod_const_mpi.F90

    r4604 r4619  
    2323    USE mod_prism
    2424#endif
    25 #ifdef CPP_XIOS
    2625    USE wxios, only: wxios_init
    27 #endif
    2826    IMPLICIT NONE
    2927
     
    4442#ifdef CPP_COUPLE
    4543!$OMP MASTER
    46 #ifdef CPP_XIOS
    47         CALL wxios_init("LMDZ", outcom=COMM_LMDZ, type_ocean=type_ocean)
    48 #else
    49         CALL prism_init_comp_proto (comp_id, 'LMDZ', ierr)
    50         CALL prism_get_localcomm_proto(COMM_LMDZ,ierr)
    51 #endif
     44        IF (using_xios) THEN
     45          CALL wxios_init("LMDZ", outcom=COMM_LMDZ, type_ocean=type_ocean)
     46        ELSE
     47          CALL prism_init_comp_proto (comp_id, 'LMDZ', ierr)
     48          CALL prism_get_localcomm_proto(COMM_LMDZ,ierr)
     49        ENDIF
    5250!$OMP END MASTER
    5351#endif
     
    6159  SUBROUTINE Init_mpi
    6260    USE lmdz_mpi
     61    USE wxios, only: wxios_init, using_xios
    6362
    64 #ifdef CPP_XIOS
    65     USE wxios, only: wxios_init
    66 #endif
    6763  IMPLICIT NONE
    6864    INTEGER             :: ierr
     
    8379! Initialisation de XIOS
    8480!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    85 #ifdef CPP_XIOS
    86       WRITE(*,*)'IN Init_mpi call wxios_init'
    87       CALL wxios_init("LMDZ", outcom=COMM_LMDZ)
    88 #endif
     81      IF (using_xios) THEN
     82        WRITE(*,*)'IN Init_mpi call wxios_init'
     83        CALL wxios_init("LMDZ", outcom=COMM_LMDZ)
     84      ENDIF
    8985!$OMP END MASTER
    9086
  • LMDZ6/trunk/libf/dyn3dmem/mod_xios_dyn3dmem.F90

    r4371 r4619  
    1212!
    1313!
    14 #ifdef CPP_XIOS
    1514
    1615MODULE mod_xios_dyn3dmem
    1716
    18      USE xios
     17     USE lmdz_xios
    1918     USE wxios, ONLY : g_comm
    2019     CHARACTER(len=100), SAVE :: dyn3d_ctx_name = "LMDZDYN"
     
    259258   
    260259END MODULE mod_xios_dyn3dmem
    261 #endif
    262 
     260
  • LMDZ6/trunk/libf/dyn3dmem/parallel_lmdz.F90

    r4600 r4619  
    384384    subroutine Finalize_parallel
    385385    USE lmdz_mpi
    386 #ifdef CPP_XIOS
    387386    ! ug Pour les sorties XIOS
    388         USE wxios
    389 #endif
     387        USE wxios
     388
    390389#ifdef CPP_COUPLE
    391390! Use of Oasis-MCT coupler
     
    416415
    417416      if (type_ocean == 'couple') then
    418 #ifdef CPP_XIOS
    419     !Fermeture propre de XIOS
    420       CALL wxios_close()
    421 #else
     417        IF (using_xios) THEN
     418          !Fermeture propre de XIOS
     419          CALL wxios_close()
     420        ELSE
    422421#ifdef CPP_COUPLE
    423          call prism_terminate_proto(ierr)
    424          IF (ierr .ne. PRISM_Ok) THEN
    425             call abort_gcm('Finalize_parallel',' Probleme dans prism_terminate_proto ',1)
    426          endif
     422           call prism_terminate_proto(ierr)
     423           IF (ierr .ne. PRISM_Ok) THEN
     424              call abort_gcm('Finalize_parallel',' Probleme dans prism_terminate_proto ',1)
     425           endif
    427426#endif
    428 #endif
     427        ENDIF
    429428      else
    430 #ifdef CPP_XIOS
    431     !Fermeture propre de XIOS
    432       CALL wxios_close()
    433 #endif
    434       IF (using_mpi) call MPI_FINALIZE(ierr)
     429        IF (using_xios) THEN
     430          !Fermeture propre de XIOS
     431          CALL wxios_close()
     432        ENDIF
     433        IF (using_mpi) call MPI_FINALIZE(ierr)
    435434      end if
    436435     
  • LMDZ6/trunk/libf/dyn3dmem/writedyn_xios.F90

    r4146 r4619  
    55     &                           masse,ps,phis)
    66
    7 #ifdef CPP_XIOS
    8       USE xios
     7      USE lmdz_xios
    98      USE parallel_lmdz
    109      USE misc_mod
     
    180179      CALL writefield_dyn_u('PS', ps(ijb:ije))
    181180
    182 #endif
    183 
    184181      END
  • LMDZ6/trunk/libf/dynphy_lonlat/phylmd/callphysiq_mod.F90

    r4146 r4619  
    2222  USE control_mod, ONLY: planet_type, ok_dyn_xios
    2323  USE physiq_mod, ONLY: physiq
    24 #ifdef CPP_XIOS
    25   USE mod_xios_dyn3dmem, ONLY : dyn3d_ctx_handle
    26   USE xios, ONLY : xios_set_current_context
    27 #endif
     24  USE lmdz_xios, ONLY : xios_set_current_context, xios_get_current_context, xios_context
    2825  IMPLICIT NONE
    2926
     
    5653  REAL,INTENT(OUT) :: zdqfi_omp(klon,llm,nqtot) ! tendency on tracers
    5754  REAL,INTENT(OUT) :: zdpsrf_omp(klon) ! tendency on surface pressure
    58  
     55  TYPE(xios_context) :: dyn3d_ctx_handle
     56
    5957  ! Local variables
    6058  CHARACTER(len=11) :: modname="call_physiq"
     
    7068  ENDIF
    7169
     70  !$OMP MASTER
     71  if (ok_dyn_xios) then
     72     CALL xios_get_current_context(dyn3d_ctx_handle)
     73  endif
     74  !$OMP END MASTER
    7275
    7376! Call physics package with required inputs/outputs
     
    9598
    9699! switching back to LMDZDYN context
    97 #ifdef CPP_XIOS
    98100!$OMP MASTER
    99101  if (ok_dyn_xios) then
     
    101103  endif
    102104!$OMP END MASTER
    103 #endif 
    104105
    105106
  • LMDZ6/trunk/libf/dynphy_lonlat/phylmd/ce0l.F90

    r4600 r4619  
    3636  USE mod_hallo,      ONLY: init_mod_hallo
    3737  USE mod_interface_dyn_phys, ONLY: init_interface_dyn_phys
    38 #ifdef CPP_XIOS
    39   USE xios, only: xios_finalize
    40 #endif
     38  USE lmdz_xios, only: xios_finalize
    4139#endif
    4240
     
    250248#ifdef CPP_PARA
    251249  END IF
    252 #ifdef CPP_XIOS
    253   CALL xios_finalize
    254 #endif
     250  IF (using_xios) CALL xios_finalize
    255251  IF (using_mpi) call MPI_FINALIZE(ierr)
    256252#endif
  • LMDZ6/trunk/libf/misc/wxios.F90

    r4608 r4619  
    11! $Id$
    2 #ifdef CPP_XIOS
     2
    33MODULE wxios
    4     USE xios
    5     USE iaxis
    6     USE iaxis_attr
    7     USE icontext_attr
    8     USE idate
    9     USE idomain_attr
    10     USE ifield_attr
    11     USE ifile_attr
    12     USE ixml_tree
     4    USE lmdz_xios
    135
    146    !Variables disponibles pendant toute l'execution du programme:
     
    411403       
    412404        !On récupère le handle:
    413         CALL xios_get_domain_handle(dom_id, dom)
     405        CALL xios_get_handle(dom_id, dom)
    414406       
    415407        !On parametrise le domaine:
    416         CALL xios_set_domain_attr_hdl(dom, ni_glo=nbp_lon, ibegin=0, ni=nbp_lon, type="rectilinear")
    417         CALL xios_set_domain_attr_hdl(dom, nj_glo=nbp_lat, jbegin=jj_begin-1, nj=jj_nb, data_dim=2)
    418         CALL xios_set_domain_attr_hdl(dom, lonvalue_1d=io_lon(1:nbp_lon), latvalue_1d=io_lat(jj_begin:jj_end))
     408        CALL xios_set_attr(dom, ni_glo=nbp_lon, ibegin=0, ni=nbp_lon, type="rectilinear")
     409        CALL xios_set_attr(dom, nj_glo=nbp_lat, jbegin=jj_begin-1, nj=jj_nb, data_dim=2)
     410        CALL xios_set_attr(dom, lonvalue_1d=io_lon(1:nbp_lon), latvalue_1d=io_lat(jj_begin:jj_end))
    419411        CALL xios_set_domain_attr("dom_out", domain_ref=dom_id)
    420412
     
    438430              WRITE(lunout,*) "wxios_domain_param: mpirank=",mpi_rank," mask(:,jj_nb)=",mask(:,jj_nb)
    439431            ENDIF
    440             CALL xios_set_domain_attr_hdl(dom, mask_2d=mask)
    441         END IF
    442 
    443          CALL xios_is_defined_domain_attr_hdl(dom,ni_glo=boool)
     432            CALL xios_set_attr(dom, mask_2d=mask)
     433        END IF
     434
     435         CALL xios_is_defined_attr(dom,ni_glo=boool)
    444436        !Vérification:
    445437        IF (xios_is_valid_domain(dom_id)) THEN
     
    480472
    481473!$OMP MASTER
    482         CALL xios_get_domain_handle(dom_id, dom)
     474        CALL xios_get_handle(dom_id, dom)
    483475       
    484476        !On parametrise le domaine:
     
    580572        IF (.NOT.xios_is_valid_file(fname)) THEN
    581573            !On créé le noeud:
    582             CALL xios_get_filegroup_handle("defile", x_fg)
    583             CALL xios_add_file(x_fg, x_file, fname)
     574            CALL xios_get_handle("defile", x_fg)
     575            CALL xios_add_child(x_fg, x_file, fname)
    584576       
    585577            !On reformate la fréquence:
     
    587579       
    588580            !On configure:
    589             CALL xios_set_file_attr_hdl(x_file, name="X"//fname,&
     581            CALL xios_set_attr(x_file, name="X"//fname,&
    590582                output_freq=nffreq, output_level=flvl, enabled=.TRUE.)
    591583       
     
    636628       
    637629        !On ajoute le champ:
    638         CALL xios_add_field(fieldgroup, field, fieldname)
     630        CALL xios_add_child(fieldgroup, field, fieldname)
    639631        !IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_field: ",fieldname,fieldgroup, fieldlongname, fieldunit
    640632       
    641633        !On rentre ses paramètres:
    642         CALL xios_set_field_attr_hdl(field, standard_name=fieldlongname, unit=newunit, default_value=def)
     634        CALL xios_set_attr(field, standard_name=fieldlongname, unit=newunit, default_value=def)
    643635        IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_field: Field ",trim(fieldname), "cree:"
    644636        IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_field: long_name=",trim(fieldlongname),"; unit=",trim(newunit),";  default_value=",nf90_fill_real
     
    691683        !On selectionne le bon groupe de champs:
    692684        IF (fdim.EQ.2) THEN
    693           CALL xios_get_fieldgroup_handle("fields_2D", fieldgroup)
     685          CALL xios_get_handle("fields_2D", fieldgroup)
    694686        ELSE
    695           CALL xios_get_fieldgroup_handle("fields_3D", fieldgroup)
     687          CALL xios_get_handle("fields_3D", fieldgroup)
    696688        ENDIF
    697689       
     
    722714            !Champ existe déjà, mais pas XML, alors on l'ajoute
    723715            !On ajoute le champ:
    724             CALL xios_get_file_handle(fname, f)
    725             CALL xios_add_fieldtofile(f, field)
     716            CALL xios_get_handle(fname, f)
     717            CALL xios_add_child(f, field)
    726718           
    727719           
    728720            !L'operation, sa frequence:
    729721            freq_op%timestep=1
    730             CALL xios_set_field_attr_hdl(field, field_ref=fieldname, operation=TRIM(ADJUSTL(operation)), freq_op=freq_op, prec=4)
     722            CALL xios_set_attr(field, field_ref=fieldname, operation=TRIM(ADJUSTL(operation)), freq_op=freq_op, prec=4)
    731723
    732724           
    733725            !On rentre ses paramètres:
    734             CALL xios_set_field_attr_hdl(field, level=field_level, enabled=.TRUE.)
     726            CALL xios_set_attr(field, level=field_level, enabled=.TRUE.)
    735727           
    736728            IF (fdim.EQ.2) THEN
     
    744736                !Si 3D :
    745737                !On ajoute l'axe vertical qui va bien:
    746                 CALL xios_set_field_attr_hdl(field, axis_ref=TRIM(ADJUSTL(axis_id)))
     738                CALL xios_set_attr(field, axis_ref=TRIM(ADJUSTL(axis_id)))
    747739               
    748740                IF (prt_level >= 10) THEN
     
    792784     END SUBROUTINE wxios_close
    793785END MODULE wxios
    794 #endif
     786
  • LMDZ6/trunk/libf/phydev/iophy.F90

    r2588 r4619  
    1313 
    1414
    15 #ifdef CPP_XIOS
    1615! interfaces for both IOIPSL and XIOS
    1716  INTERFACE histwrite_phy
    1817    MODULE PROCEDURE histwrite2d_phy,histwrite3d_phy,histwrite2d_xios,histwrite3d_xios
    1918  END INTERFACE
    20 #else
    21 ! interfaces for IOIPSL
    22   INTERFACE histwrite_phy
    23     MODULE PROCEDURE histwrite2d_phy,histwrite3d_phy
    24   END INTERFACE
    25 #endif
    26 
    27 #ifdef CPP_XIOS
     19
    2820! interfaces for both IOIPSL and XIOS
    2921  INTERFACE histbeg_phy_all
    3022    MODULE PROCEDURE histbeg_phy, histbeg_phyxios
    3123  END INTERFACE
    32 #else
    33 ! interfaces for IOIPSL
    34   INTERFACE histbeg_phy_all
    35     MODULE PROCEDURE histbeg_phy
    36   END INTERFACE
    37 #endif
    3824
    3925contains
     
    5137  USE ioipsl, only: flio_dom_set
    5238#endif
    53 #ifdef CPP_XIOS
    54   use wxios, only: wxios_domain_param
    55 #endif
     39  use wxios, only: wxios_domain_param, using_xios
    5640  implicit none
    5741    real,dimension(klon),intent(in) :: rlon
     
    122106                      'APPLE',phys_domain_id)
    123107#endif
    124 #ifdef CPP_XIOS
    125     ! Set values for the mask:
    126     IF (mpi_rank == 0) THEN
    127         data_ibegin = 0
    128     ELSE
    129         data_ibegin = ii_begin - 1
    130     END IF
    131 
    132     IF (mpi_rank == mpi_size-1) THEN
    133         data_iend = nbp_lon
    134     ELSE
    135         data_iend = ii_end + 1
    136     END IF
    137 
    138     if (prt_level>=10) then
    139       write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," iibegin=",ii_begin , " ii_end=",ii_end," jjbegin=",jj_begin," jj_nb=",jj_nb," jj_end=",jj_end
    140       write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," nbp_lon=",nbp_lon," nbp_lat=",nbp_lat
    141       write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," data_ibegin=",data_ibegin," data_iend=",data_iend
    142       write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," data_ibegin=",data_ibegin," data_iend=",data_iend
    143       write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," is_south_pole=",is_south_pole_dyn
    144     endif
    145 
    146     ! Initialize the XIOS domain coreesponding to this process:
    147     CALL wxios_domain_param("dom_glo", is_sequential, nbp_lon, jj_nb, nbp_lon, nbp_lat, &
    148                             1, nbp_lon, ii_begin, ii_end, jj_begin, jj_end,             &
    149                             klon_mpi+2*(nbp_lon-1), data_ibegin, data_iend,             &
    150                             io_lat, io_lon,is_south_pole_dyn,mpi_rank)
    151 #endif
     108    IF (using_xios) THEN
     109      ! Set values for the mask:
     110      IF (mpi_rank == 0) THEN
     111          data_ibegin = 0
     112      ELSE
     113          data_ibegin = ii_begin - 1
     114      END IF
     115
     116      IF (mpi_rank == mpi_size-1) THEN
     117          data_iend = nbp_lon
     118      ELSE
     119          data_iend = ii_end + 1
     120      END IF
     121
     122      if (prt_level>=10) then
     123        write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," iibegin=",ii_begin , " ii_end=",ii_end," jjbegin=",jj_begin," jj_nb=",jj_nb," jj_end=",jj_end
     124        write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," nbp_lon=",nbp_lon," nbp_lat=",nbp_lat
     125        write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," data_ibegin=",data_ibegin," data_iend=",data_iend
     126        write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," data_ibegin=",data_ibegin," data_iend=",data_iend
     127        write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," is_south_pole=",is_south_pole_dyn
     128      endif
     129
     130      ! Initialize the XIOS domain coreesponding to this process:
     131      CALL wxios_domain_param("dom_glo", is_sequential, nbp_lon, jj_nb, nbp_lon, nbp_lat, &
     132                              1, nbp_lon, ii_begin, ii_end, jj_begin, jj_end,             &
     133                              klon_mpi+2*(nbp_lon-1), data_ibegin, data_iend,             &
     134                              io_lat, io_lon,is_south_pole_dyn,mpi_rank)
     135    ENDIF
    152136!$OMP END MASTER
    153137     
     
    184168!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    185169
    186 #ifdef CPP_XIOS
    187170
    188171! SUBROUTINE histbeg_phyxios(name,itau0,zjulian,dtime,ffreq,lev,nhori,nid_day)
     
    213196  END SUBROUTINE histbeg_phyxios
    214197
    215 #endif
    216198
    217199!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    339321
    340322! VERSION DES HISTWRITE DEDIEES AU TOUT-XIOS-XML DEJA UTILISEE DANS PHYDEV
    341 #ifdef CPP_XIOS
     323
    342324  SUBROUTINE histwrite2d_xios(field_name,field)
    343325  USE dimphy, only: klon
    344326  USE mod_phys_lmdz_para, only: gather_omp, grid1Dto2D_mpi, &
    345327                                jj_nb, klon_mpi
    346   USE xios, only: xios_send_field
     328  USE lmdz_xios, only: xios_send_field
    347329  USE print_control_mod, ONLY: prt_level, lunout
    348330  USE mod_grid_phy_lmdz, ONLY: nbp_lon
     
    368350    IF (prt_level >= 10) WRITE(lunout,*)'End histrwrite2d_xios ',trim(field_name)
    369351  END SUBROUTINE histwrite2d_xios
    370 #endif
    371352
    372353!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    373354
    374355! VERSION DES HISTWRITE DEDIEES AU TOUT-XIOS-XML DEJA UTILISEE DANS PHYDEV
    375 #ifdef CPP_XIOS
     356
    376357  SUBROUTINE histwrite3d_xios(field_name, field)
    377358  USE dimphy, only: klon, klev
    378359  USE mod_phys_lmdz_para, only: gather_omp, grid1Dto2D_mpi, &
    379360                                jj_nb, klon_mpi
    380   USE xios, only: xios_send_field
     361  USE lmdz_xios, only: xios_send_field
    381362  USE print_control_mod, ONLY: prt_level,lunout
    382363  USE mod_grid_phy_lmdz, ONLY: nbp_lon
     
    407388    IF (prt_level >= 10) write(lunout,*)'End histrwrite3d_xios ',trim(field_name)
    408389  END SUBROUTINE histwrite3d_xios
    409 #endif
    410390
    411391end module iophy
  • LMDZ6/trunk/libf/phydev/physiq_mod.F90

    r2643 r4619  
    2323      USE mod_grid_phy_lmdz, ONLY: nbp_lon,nbp_lat
    2424
    25 #ifdef CPP_XIOS
    26       USE xios, ONLY: xios_update_calendar
     25      USE lmdz_xios, ONLY: xios_update_calendar, using_xios
    2726      USE wxios, only: wxios_add_vaxis, wxios_set_cal, wxios_closedef
    2827      USE iophy, ONLY: histwrite_phy
    29 #endif
    3028
    3129      IMPLICIT none
     
    126124#endif
    127125
    128 #ifdef CPP_XIOS
     126    IF (using_xios) THEN
    129127!XIOS
    130     ! Declare available vertical axes to be used in output files:   
    131     CALL wxios_add_vaxis("presnivs", klev, presnivs)
     128      ! Declare available vertical axes to be used in output files:   
     129      CALL wxios_add_vaxis("presnivs", klev, presnivs)
    132130
    133     ! Declare calendar and time step
    134     CALL wxios_set_cal(dtime,"earth_360d",1,1,1,0.0,1,1,1,0.0)
     131      ! Declare calendar and time step
     132      CALL wxios_set_cal(dtime,"earth_360d",1,1,1,0.0,1,1,1,0.0)
    135133   
    136     !Finalize the context:
    137     CALL wxios_closedef()
    138 #endif
     134      !Finalize the context:
     135      CALL wxios_closedef()
     136    ENDIF
    139137!$OMP END MASTER
    140138!$OMP BARRIER
     
    176174
    177175!XIOS
    178 #ifdef CPP_XIOS
    179 !$OMP MASTER
     176IF (using_xios) THEN
     177  !$OMP MASTER
    180178    !Increment XIOS time
    181179    CALL xios_update_calendar(itau)
    182 !$OMP END MASTER
    183 !$OMP BARRIER
     180  !$OMP END MASTER
     181  !$OMP BARRIER
    184182
    185183    !Send fields to XIOS: (NB these fields must also be defined as
     
    190188    CALL histwrite_phy("v",v)
    191189    CALL histwrite_phy("ps",paprs(:,1))
    192 #endif
     190ENDIF
    193191
    194192! if lastcall, then it is time to write "restartphy.nc" file
  • 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
  • LMDZ6/trunk/libf/phylmd/cosp/cosp_output_mod.F90

    r3308 r4619  
    235235  USE time_phylmdz_mod, ONLY: day_ref, annee_ref, day_ini, start_time, itau_phy
    236236  USE print_control_mod, ONLY: lunout
    237 
    238 #ifdef CPP_XIOS
    239     ! ug Pour les sorties XIOS
    240     USE wxios
    241 #endif
     237  ! ug Pour les sorties XIOS
     238  USE wxios
    242239
    243240  IMPLICIT NONE
     
    263260!!! Variables d'entree
    264261
    265 #ifdef CPP_XIOS
    266     ! ug Variables utilisées pour récupérer le calendrier pour xios
    267     INTEGER :: x_an, x_mois, x_jour
    268     REAL :: x_heure
    269     INTEGER :: ini_an, ini_mois, ini_jour
    270     REAL :: ini_heure
    271 #endif
     262  ! ug Variables utilisées pour récupérer le calendrier pour xios
     263  INTEGER :: x_an, x_mois, x_jour
     264  REAL :: x_heure
     265  INTEGER :: ini_an, ini_mois, ini_jour
     266  REAL :: ini_heure
    272267
    273268    WRITE(lunout,*) 'Debut cosp_output_mod.F90'
     
    316311    CALL ymds2ju(annee_ref, 1, day_ini, start_time, zjulian_start)
    317312
    318 #ifdef CPP_XIOS
     313    IF (using_xios) THEN
    319314   
    320 ! recuperer la valeur indefine Xios
    321 !    CALL xios_get_field_attr("clcalipso",default_value=Cosp_fill_value)
    322 !         Cosp_fill_value=missing_val
    323           Cosp_fill_value=0.
    324          print*,'Cosp_fill_value=',Cosp_fill_value
    325 !    if (use_vgrid) then
    326 !      print*,'vgrid%Nlvgrid, vgrid%z = ',vgrid%Nlvgrid, vgrid%z
    327         CALL wxios_add_vaxis("height", vgrid%Nlvgrid, vgrid%z)
    328      print*,'wxios_add_vaxis '
    329 !    else
    330 !         WRITE(lunout,*) 'wxios_add_vaxis "presnivs", vgrid%Nlvgrid ',vgrid%Nlvgrid
    331 !        CALL wxios_add_vaxis("presnivs", vgrid%Nlvgrid, presnivs)
    332 !    endif
    333     WRITE(lunout,*) 'wxios_add_vaxis height_mlev, Nlevlmdz ',Nlevlmdz
    334     CALL wxios_add_vaxis("height_mlev", Nlevlmdz, vgrid%mz)
    335     WRITE(lunout,*) 'wxios_add_vaxis sza, PARASOL_NREFL ',PARASOL_NREFL
    336     CALL wxios_add_vaxis("sza", PARASOL_NREFL, PARASOL_SZA)
    337     WRITE(lunout,*) 'wxios_add_vaxis pressure2 ',7
    338     CALL wxios_add_vaxis("pressure2", 7, ISCCP_PC)
    339     WRITE(lunout,*) 'wxios_add_vaxis column ',Ncolumns
    340     CALL wxios_add_vaxis("column", Ncolumns, column_ax)
    341 
    342 ! AI nov 2015
    343    CALL wxios_add_vaxis("temp", LIDAR_NTEMP, LIDAR_PHASE_TEMP)
    344    CALL wxios_add_vaxis("cth", MISR_N_CTH, MISR_CTH)
    345    CALL wxios_add_vaxis("dbze", DBZE_BINS, dbze_ax)
    346    CALL wxios_add_vaxis("scatratio", SR_BINS, sratio_ax)
    347    CALL wxios_add_vaxis("ReffIce", numMODISReffIceBins, reffICE_binCenters)
    348    CALL wxios_add_vaxis("ReffLiq", numMODISReffLiqBins, reffLIQ_binCenters)
    349    print*,'reffICE_binCenters=',reffICE_binCenters
    350    CALL wxios_add_vaxis("tau", 7, ISCCP_TAU)
    351 
    352 #endif
     315  ! recuperer la valeur indefine Xios
     316  !    CALL xios_get_field_attr("clcalipso",default_value=Cosp_fill_value)
     317  !         Cosp_fill_value=missing_val
     318            Cosp_fill_value=0.
     319           print*,'Cosp_fill_value=',Cosp_fill_value
     320  !    if (use_vgrid) then
     321  !      print*,'vgrid%Nlvgrid, vgrid%z = ',vgrid%Nlvgrid, vgrid%z
     322          CALL wxios_add_vaxis("height", vgrid%Nlvgrid, vgrid%z)
     323       print*,'wxios_add_vaxis '
     324  !    else
     325  !         WRITE(lunout,*) 'wxios_add_vaxis "presnivs", vgrid%Nlvgrid ',vgrid%Nlvgrid
     326  !        CALL wxios_add_vaxis("presnivs", vgrid%Nlvgrid, presnivs)
     327  !    endif
     328      WRITE(lunout,*) 'wxios_add_vaxis height_mlev, Nlevlmdz ',Nlevlmdz
     329      CALL wxios_add_vaxis("height_mlev", Nlevlmdz, vgrid%mz)
     330      WRITE(lunout,*) 'wxios_add_vaxis sza, PARASOL_NREFL ',PARASOL_NREFL
     331      CALL wxios_add_vaxis("sza", PARASOL_NREFL, PARASOL_SZA)
     332      WRITE(lunout,*) 'wxios_add_vaxis pressure2 ',7
     333      CALL wxios_add_vaxis("pressure2", 7, ISCCP_PC)
     334      WRITE(lunout,*) 'wxios_add_vaxis column ',Ncolumns
     335      CALL wxios_add_vaxis("column", Ncolumns, column_ax)
     336
     337  ! AI nov 2015
     338     CALL wxios_add_vaxis("temp", LIDAR_NTEMP, LIDAR_PHASE_TEMP)
     339     CALL wxios_add_vaxis("cth", MISR_N_CTH, MISR_CTH)
     340     CALL wxios_add_vaxis("dbze", DBZE_BINS, dbze_ax)
     341     CALL wxios_add_vaxis("scatratio", SR_BINS, sratio_ax)
     342     CALL wxios_add_vaxis("ReffIce", numMODISReffIceBins, reffICE_binCenters)
     343     CALL wxios_add_vaxis("ReffLiq", numMODISReffLiqBins, reffLIQ_binCenters)
     344     print*,'reffICE_binCenters=',reffICE_binCenters
     345     CALL wxios_add_vaxis("tau", 7, ISCCP_TAU)
     346
     347  ENDIF
    353348   
    354349    zdtimemoy_cosp = freq_COSP         ! Frequence ou l on moyenne
     
    363358!                    nhoricosp(iff),cosp_nidfiles(iff)
    364359
    365 #ifdef CPP_XIOS
    366         IF (.not. ok_all_xml) then
    367          WRITE(lunout,*) 'wxios_add_file ',cosp_outfilenames(iff)
    368          CALL wxios_add_file(cosp_outfilenames(iff),chfreq(iff),10)
    369         ENDIF
    370 #endif
     360         IF (using_xios) THEN
     361           IF (.not. ok_all_xml) then
     362             WRITE(lunout,*) 'wxios_add_file ',cosp_outfilenames(iff)
     363             CALL wxios_add_file(cosp_outfilenames(iff),chfreq(iff),10)
     364           ENDIF
     365         ENDIF
    371366
    372367#ifndef CPP_IOIPSL_NO_OUTPUT
  • LMDZ6/trunk/libf/phylmd/cosp/cosp_output_write_mod.F90

    r3308 r4619  
    2626    USE time_phylmdz_mod, ONLY: itau_phy, start_time, day_step_phy
    2727    USE print_control_mod, ONLY: lunout,prt_level
    28 
    29 #ifdef CPP_XIOS
    3028    USE wxios, only: wxios_closedef
    31     USE xios, only: xios_update_calendar, xios_field_is_active
    32 #endif
     29    USE lmdz_xios, only: xios_update_calendar, xios_field_is_active, using_xios
    3330  IMPLICIT NONE 
    3431!!! Variables d'entree
     
    5855  real, dimension(Npoints,MISR_N_CTH,7) :: tmp_fi4da_misr
    5956
    60 #ifdef CPP_XIOS
    61   missing_val=missing_cosp
    62 #else
    63   missing_val=0.
    64 #endif
     57  IF (using_xios) THEN
     58    missing_val=missing_cosp
     59  ELSE
     60    missing_val=0.
     61  ENDIF
    6562
    6663  Nlevout = vgrid%Nlvgrid
     
    9087!   endif
    9188
    92 !!#ifdef CPP_XIOS
     89!!IF (using_xios) THEN
    9390! !$OMP MASTER
    9491!IF (cosp_varsdefined) THEN
     
    10198!  !$OMP END MASTER
    10299!  !$OMP BARRIER
    103 !!#endif
     100!!ENDIF
    104101
    105102!!!! Sorties Calipso
     
    163160   if (cfg%Lproftemp) CALL histwrite3d_cosp(o_proftemp,stlidar%proftemp,nvert)                    !TIBO
    164161
    165 #ifdef CPP_XIOS
    166    do icl=1,SR_BINS
    167       tmp_fi4da_cfadL(:,:,icl)=stlidar%cfad_sr(:,icl,:)
    168    enddo
    169 !   if (cfg%LcfadLidarsr532) CALL histwrite4d_cosp(o_cfad_lidarsr532,stlidar%cfad_sr)
    170    if (cfg%LcfadLidarsr532) CALL histwrite4d_cosp(o_cfad_lidarsr532,tmp_fi4da_cfadL)
    171    if (cfg%LprofSR) CALL histwrite4d_cosp(o_profSR,stlidar%profSR)                              !TIBO
    172 #else
    173    if (cfg%LcfadLidarsr532) then
     162   IF (using_xios) THEN
    174163     do icl=1,SR_BINS
    175         CALL histwrite3d_cosp(o_cfad_lidarsr532,stlidar%cfad_sr(:,icl,:),nvert,icl)
     164        tmp_fi4da_cfadL(:,:,icl)=stlidar%cfad_sr(:,icl,:)
    176165     enddo
    177    endif
    178    if (cfg%LprofSR) then
    179      do icl=1,Ncolumns                                                              !TIBO
    180         CALL histwrite3d_cosp(o_profSR,stlidar%profSR(:,icl,:),nvert,icl)           !TIBO
    181      enddo                                                                          !TIBO
    182    endif
    183 #endif
     166  !   if (cfg%LcfadLidarsr532) CALL histwrite4d_cosp(o_cfad_lidarsr532,stlidar%cfad_sr)
     167     if (cfg%LcfadLidarsr532) CALL histwrite4d_cosp(o_cfad_lidarsr532,tmp_fi4da_cfadL)
     168     if (cfg%LprofSR) CALL histwrite4d_cosp(o_profSR,stlidar%profSR)                              !TIBO
     169   ELSE
     170     if (cfg%LcfadLidarsr532) then
     171       do icl=1,SR_BINS
     172          CALL histwrite3d_cosp(o_cfad_lidarsr532,stlidar%cfad_sr(:,icl,:),nvert,icl)
     173       enddo
     174     endif
     175     if (cfg%LprofSR) then
     176       do icl=1,Ncolumns                                                              !TIBO
     177          CALL histwrite3d_cosp(o_profSR,stlidar%profSR(:,icl,:),nvert,icl)           !TIBO
     178       enddo                                                                          !TIBO
     179      endif
     180   ENDIF
     181
    184182   if (cfg%LparasolRefl) CALL histwrite3d_cosp(o_parasol_refl,stlidar%parasolrefl,nvertp)
    185183
     
    201199  endif
    202200
    203 #ifdef CPP_XIOS
    204    if (cfg%Latb532) CALL histwrite4d_cosp(o_atb532,sglidar%beta_tot)
    205 #else
    206    if (cfg%Latb532) then 
    207      do icl=1,Ncolumns
    208         CALL histwrite3d_cosp(o_atb532,sglidar%beta_tot(:,icl,:),nvertmcosp,icl)
    209      enddo
    210    endif
    211 #endif
     201   IF (using_xios) THEN
     202     if (cfg%Latb532) CALL histwrite4d_cosp(o_atb532,sglidar%beta_tot)
     203   ELSE
     204     if (cfg%Latb532) then 
     205       do icl=1,Ncolumns
     206          CALL histwrite3d_cosp(o_atb532,sglidar%beta_tot(:,icl,:),nvertmcosp,icl)
     207       enddo
     208     endif
     209   ENDIF
    212210
    213211   if (cfg%LlidarBetaMol532) CALL histwrite3d_cosp(o_beta_mol532,sglidar%beta_mol,nvertmcosp)
     
    219217
    220218   where(stradar%cfad_ze == R_UNDEF) stradar%cfad_ze = missing_val
    221 #ifdef CPP_XIOS
    222    do icl=1,DBZE_BINS
    223      tmp_fi4da_cfadR(:,:,icl)=stradar%cfad_ze(:,icl,:)
    224    enddo
    225    if (cfg%Ldbze94) CALL histwrite4d_cosp(o_dbze94,sgradar%Ze_tot)
    226 !   if (cfg%LcfadDbze94) CALL histwrite4d_cosp(o_cfadDbze94,stradar%cfad_ze)
    227    if (cfg%LcfadDbze94) CALL histwrite4d_cosp(o_cfadDbze94,tmp_fi4da_cfadR)
    228 #else
    229    if (cfg%Ldbze94) then
    230     do icl=1,Ncolumns
    231        CALL histwrite3d_cosp(o_dbze94,sgradar%Ze_tot(:,icl,:),nvert,icl)
    232     enddo
    233    endif
    234    if (cfg%LcfadDbze94) then
    235     do icl=1,DBZE_BINS
    236     CALL histwrite3d_cosp(o_cfadDbze94,stradar%cfad_ze(:,icl,:),nvert,icl)
    237     enddo
    238    endif
    239 #endif
     219   IF (using_xios) THEN
     220     do icl=1,DBZE_BINS
     221       tmp_fi4da_cfadR(:,:,icl)=stradar%cfad_ze(:,icl,:)
     222     enddo
     223     if (cfg%Ldbze94) CALL histwrite4d_cosp(o_dbze94,sgradar%Ze_tot)
     224  !  if (cfg%LcfadDbze94) CALL histwrite4d_cosp(o_cfadDbze94,stradar%cfad_ze)
     225     if (cfg%LcfadDbze94) CALL histwrite4d_cosp(o_cfadDbze94,tmp_fi4da_cfadR)
     226   ELSE
     227     if (cfg%Ldbze94) then
     228       do icl=1,Ncolumns
     229         CALL histwrite3d_cosp(o_dbze94,sgradar%Ze_tot(:,icl,:),nvert,icl)
     230       enddo
     231     endif
     232     if (cfg%LcfadDbze94) then
     233       do icl=1,DBZE_BINS
     234         CALL histwrite3d_cosp(o_cfadDbze94,stradar%cfad_ze(:,icl,:),nvert,icl)
     235       enddo
     236     endif
     237   ENDIF
    240238 endif
    241239! endif pour radar
     
    264262
    265263   CALL histwrite2d_cosp(o_sunlit,gbx%sunlit)
    266 #ifdef CPP_XIOS
    267   if (cfg%Lclisccp) CALL histwrite4d_cosp(o_clisccp2,isccp%fq_isccp)
    268 #else
    269    if (cfg%Lclisccp) then
    270      do icl=1,7
    271        CALL histwrite3d_cosp(o_clisccp2,isccp%fq_isccp(:,icl,:),nvertisccp,icl)
    272      enddo
    273    endif
    274 #endif
     264   IF (using_xios) THEN
     265     if (cfg%Lclisccp) CALL histwrite4d_cosp(o_clisccp2,isccp%fq_isccp)
     266   ELSE
     267     if (cfg%Lclisccp) then
     268       do icl=1,7
     269         CALL histwrite3d_cosp(o_clisccp2,isccp%fq_isccp(:,icl,:),nvertisccp,icl)
     270       enddo
     271     endif
     272   ENDIF
    275273
    276274   if (cfg%Lboxtauisccp) CALL histwrite3d_cosp(o_boxtauisccp,isccp%boxtau,nvertcol)
     
    288286   where(misr%fq_MISR == R_UNDEF) misr%fq_MISR = missing_val
    289287
    290 #ifdef CPP_XIOS
    291    do icl=1,MISR_N_CTH
    292       tmp_fi4da_misr(:,icl,:)=misr%fq_MISR(:,:,icl)
    293    enddo
    294 !   if (cfg%LclMISR) CALL histwrite4d_cosp(o_clMISR,misr%fq_MISR)
    295    if (cfg%LclMISR) CALL histwrite4d_cosp(o_clMISR,tmp_fi4da_misr)
    296 #else
    297    if (cfg%LclMISR) then
    298     do icl=1,7
    299       CALL histwrite3d_cosp(o_clMISR,misr%fq_MISR(:,icl,:),nvertmisr,icl)
    300     enddo
    301    endif
    302 #endif
     288   IF (using_xios) THEN
     289     do icl=1,MISR_N_CTH
     290        tmp_fi4da_misr(:,icl,:)=misr%fq_MISR(:,:,icl)
     291     enddo
     292  !   if (cfg%LclMISR) CALL histwrite4d_cosp(o_clMISR,misr%fq_MISR)
     293     if (cfg%LclMISR) CALL histwrite4d_cosp(o_clMISR,tmp_fi4da_misr)
     294   ELSE
     295     if (cfg%LclMISR) then
     296      do icl=1,7
     297        CALL histwrite3d_cosp(o_clMISR,misr%fq_MISR(:,icl,:),nvertmisr,icl)
     298      enddo
     299     endif
     300   ENDIF
    303301 endif
    304302! endif pour Misr
     
    365363          modis%Optical_Thickness_vs_Cloud_Top_Pressure = missing_val
    366364
    367 #ifdef CPP_XIOS
    368    if (cfg%Lclmodis) CALL histwrite4d_cosp(o_clmodis,modis%Optical_Thickness_vs_Cloud_Top_Pressure)
    369 #else
    370   if (cfg%Lclmodis) then
    371    do icl=1,7
    372    CALL histwrite3d_cosp(o_clmodis, &
    373      modis%Optical_Thickness_vs_Cloud_Top_Pressure(:,icl,:),nvertisccp,icl)           
    374    enddo
    375   endif
    376 #endif
     365   IF (using_xios) THEN
     366     if (cfg%Lclmodis) CALL histwrite4d_cosp(o_clmodis,modis%Optical_Thickness_vs_Cloud_Top_Pressure)
     367   ELSE
     368     if (cfg%Lclmodis) then
     369       do icl=1,7
     370         CALL histwrite3d_cosp(o_clmodis, &
     371         modis%Optical_Thickness_vs_Cloud_Top_Pressure(:,icl,:),nvertisccp,icl)           
     372       enddo
     373      endif
     374   ENDIF
    377375
    378376    where(modis%Optical_Thickness_vs_ReffIce == R_UNDEF) &
     
    382380          modis%Optical_Thickness_vs_ReffLiq = missing_val
    383381
    384 #ifdef CPP_XIOS
    385   if (cfg%Lcrimodis) CALL histwrite4d_cosp(o_crimodis,modis%Optical_Thickness_vs_ReffIce)
    386   if (cfg%Lcrlmodis) CALL histwrite4d_cosp(o_crlmodis,modis%Optical_Thickness_vs_ReffLiq)
    387 #else
    388   if (cfg%Lcrimodis) then
    389     do icl=1,7
    390      CALL histwrite3d_cosp(o_crimodis, &
    391           modis%Optical_Thickness_vs_ReffIce(:,icl,:),nvertReffIce,icl)
    392     enddo
    393   endif
    394   if (cfg%Lcrlmodis) then
    395     do icl=1,7
    396      CALL histwrite3d_cosp(o_crlmodis, &
    397           modis%Optical_Thickness_vs_ReffLiq(:,icl,:),nvertReffLiq,icl)
    398     enddo
    399   endif
    400 #endif
     382   IF (using_xios) THEN
     383     if (cfg%Lcrimodis) CALL histwrite4d_cosp(o_crimodis,modis%Optical_Thickness_vs_ReffIce)
     384     if (cfg%Lcrlmodis) CALL histwrite4d_cosp(o_crlmodis,modis%Optical_Thickness_vs_ReffLiq)
     385   ELSE
     386     if (cfg%Lcrimodis) then
     387       do icl=1,7
     388         CALL histwrite3d_cosp(o_crimodis, &
     389            modis%Optical_Thickness_vs_ReffIce(:,icl,:),nvertReffIce,icl)
     390       enddo
     391     endif
     392     if (cfg%Lcrlmodis) then
     393       do icl=1,7
     394         CALL histwrite3d_cosp(o_crlmodis, &
     395            modis%Optical_Thickness_vs_ReffLiq(:,icl,:),nvertReffLiq,icl)
     396       enddo
     397     endif
     398   ENDIF
    401399 endif !modis
    402400
     
    410408            ENDDO !  iff
    411409#endif
    412 ! Fermeture dans phys_output_write
    413 !#ifdef CPP_XIOS
    414             !On finalise l'initialisation:
    415             !CALL wxios_closedef()
    416 !#endif
    417410
    418411!$OMP END MASTER
     
    451444    USE mod_grid_phy_lmdz, ONLY: nbp_lon
    452445    USE print_control_mod, ONLY: lunout,prt_level
    453 #ifdef CPP_XIOS
    454   USE wxios
    455 #endif
     446    USE wxios
    456447
    457448    IMPLICIT NONE
     
    485476    ENDIF
    486477
    487 #ifdef CPP_XIOS
    488      IF (.not. ok_all_xml) then
    489        IF ( var%cles(iff) ) THEN
    490          if (prt_level >= 10) then
    491               WRITE(lunout,*)'Appel wxios_add_field_to_file var%name =',var%name
    492          endif
    493         CALL wxios_add_field_to_file(var%name, 2, cosp_nidfiles(iff), cosp_outfilenames(iff), &
     478    IF (using_xios) THEN
     479      IF (.not. ok_all_xml) then
     480        IF ( var%cles(iff) ) THEN
     481          if (prt_level >= 10) then
     482            WRITE(lunout,*)'Appel wxios_add_field_to_file var%name =',var%name
     483          endif
     484          CALL wxios_add_field_to_file(var%name, 2, cosp_nidfiles(iff), cosp_outfilenames(iff), &
    494485                                     var%description, var%unit, 1, typeecrit)
    495        ENDIF
    496      ENDIF
    497 #endif
     486        ENDIF
     487      ENDIF
     488    ENDIF
    498489
    499490#ifndef CPP_IOIPSL_NO_OUTPUT
     
    514505    USE mod_grid_phy_lmdz, ONLY: nbp_lon
    515506    USE print_control_mod, ONLY: lunout,prt_level
    516 
    517 #ifdef CPP_XIOS
    518   USE wxios
    519 #endif
    520 
     507    USE wxios
    521508
    522509    IMPLICIT NONE
     
    591578    ENDIF
    592579
    593 #ifdef CPP_XIOS
     580    IF (using_xios) THEN
    594581      IF (.not. ok_all_xml) then
    595582        IF ( var%cles(iff) ) THEN
     
    601588        ENDIF
    602589      ENDIF
    603 #endif
     590    ENDIF
    604591
    605592#ifndef CPP_IOIPSL_NO_OUTPUT
     
    621608  USE mod_grid_phy_lmdz, ONLY: nbp_lon
    622609  USE print_control_mod, ONLY: lunout,prt_level
    623 
    624 #ifdef CPP_XIOS
    625   USE xios, only: xios_send_field
    626 #endif
     610  USE lmdz_xios, only: xios_send_field, using_xios
    627611
    628612  IMPLICIT NONE
     
    672656        CALL histwrite(cosp_nidfiles(iff),var%name,itau_iocosp,Field2d,nbp_lon*jj_nb,index2d)
    673657#endif
    674                 deallocate(index2d)
    675 #ifdef CPP_XIOS
     658            deallocate(index2d)
     659            IF (using_xios) THEN
    676660              IF (.not. ok_all_xml) then
    677661                 if (firstx) then
     
    683667                 endif
    684668              ENDIF
    685 #endif
    686            ENDIF
     669            ENDIF
     670          ENDIF
    687671      ENDDO
    688672
    689 #ifdef CPP_XIOS
     673    IF (using_xios) THEN
    690674      IF (ok_all_xml) THEN
    691675        if (prt_level >= 1) then
     
    694678       CALL xios_send_field(var%name, Field2d)
    695679      ENDIF
    696 #endif
     680    ENDIF
    697681
    698682!$OMP END MASTER   
     
    710694  USE mod_grid_phy_lmdz, ONLY: nbp_lon
    711695  USE print_control_mod, ONLY: lunout,prt_level
    712 
    713 #ifdef CPP_XIOS
    714   USE xios, only: xios_send_field
    715 #endif
    716 
     696  USE lmdz_xios, only: xios_send_field, using_xios
    717697
    718698  IMPLICIT NONE
     
    776756#endif
    777757
    778 #ifdef CPP_XIOS
     758        IF (using_xios) THEN
    779759          IF (.not. ok_all_xml) then
    780760           IF (firstx) THEN
     
    784764           ENDIF
    785765          ENDIF
    786 #endif
     766        ENDIF
    787767         deallocate(index3d)
    788768        ENDIF
    789769      ENDDO
    790 #ifdef CPP_XIOS
     770
     771  IF (using_xios) THEN
    791772    IF (ok_all_xml) THEN
    792773     CALL xios_send_field(nom, Field3d(:,:,1:nlev))
    793774     IF (prt_level >= 1) WRITE(lunout,*)'xios_send_field ',var%name
    794775    ENDIF
    795 #endif
     776  ENDIF
    796777
    797778!$OMP END MASTER   
     
    809790  USE mod_grid_phy_lmdz, ONLY: nbp_lon
    810791  USE print_control_mod, ONLY: lunout,prt_level
    811 
    812 #ifdef CPP_XIOS
    813   USE xios, only: xios_send_field
    814 #endif
    815 
     792  USE lmdz_xios, only: xios_send_field, using_xios
    816793
    817794  IMPLICIT NONE
     
    842819    CALL grid1Dto2D_mpi(buffer_omp,field4d)
    843820
    844 #ifdef CPP_XIOS
     821   IF (using_xios) THEN
    845822!    IF (ok_all_xml) THEN
    846823     CALL xios_send_field(var%name, Field4d(:,:,1:nlev,1:nlev2))
    847824     IF (prt_level >= 1) WRITE(lunout,*)'xios_send_field ',var%name
    848825!    ENDIF
    849 #endif
     826   ENDIF
    850827
    851828!$OMP END MASTER   
  • LMDZ6/trunk/libf/phylmd/cosp/cosp_read_otputkeys.F90

    r3377 r4619  
    226226
    227227 SUBROUTINE READ_COSP_OUTPUT_NL(itap,cosp_nl,cfg)
    228 
    229 #ifdef CPP_XIOS
    230     USE xios, ONLY: xios_field_is_active
    231 #endif
     228    USE lmdz_xios, ONLY: xios_field_is_active, using_xios
    232229  implicit none
    233230  character(len=*),intent(in) :: cosp_nl
     
    746743    USE MOD_COSP_CONSTANTS
    747744    USE MOD_COSP_TYPES
    748 #ifdef CPP_XIOS
    749     USE xios, ONLY: xios_field_is_active
    750 #endif
     745    USE lmdz_xios, ONLY: xios_field_is_active,using_xios
    751746  implicit none
    752747  type(cosp_config),intent(out) :: cfg
    753748  integer :: i
    754 
    755 #ifdef CPP_XIOS
    756749
    757750 logical :: Lradar_sim,Llidar_sim,Lisccp_sim,Lmodis_sim,Lmisr_sim,Lrttov_sim, Lstats, &
     
    776769  character(len=32) :: out_list(N_OUT_LIST)
    777770
    778   do i=1,N_OUT_LIST
    779     cfg%out_list(i)=''
    780   enddo
     771  IF (using_xios) THEN
     772   
     773    do i=1,N_OUT_LIST
     774      cfg%out_list(i)=''
     775    enddo
    781776
    782777    LcfadDbze94   = .false.
     
    12321227  cfg%Lrttov_sim = Lrttov_sim
    12331228
    1234 #endif
     1229 ENDIF ! using_xios
    12351230
    12361231  END SUBROUTINE read_xiosfieldactive
  • LMDZ6/trunk/libf/phylmd/cosp/mod_cosp.F90

    r4593 r4619  
    2323! OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
    2424
    25 INCLUDE "cosp_defs.h"
     25#include "cosp_defs.h"
    2626MODULE MOD_COSP
    2727  USE MOD_COSP_TYPES
  • LMDZ6/trunk/libf/phylmd/cosp/mod_cosp_constants.F90

    r4593 r4619  
    3333!
    3434
    35 INCLUDE "cosp_defs.h"
     35#INCLUDE "cosp_defs.h"
    3636MODULE MOD_COSP_CONSTANTS
    3737    IMPLICIT NONE
  • LMDZ6/trunk/libf/phylmd/cosp/mod_cosp_simulator.F90

    r4593 r4619  
    3131!
    3232
    33 INCLUDE "cosp_defs.h"
     33#include "cosp_defs.h"
    3434MODULE MOD_COSP_SIMULATOR
    3535  USE MOD_COSP_CONSTANTS, ONLY: I_RADAR, I_LIDAR, I_ISCCP, I_MISR, I_MODIS, &
  • LMDZ6/trunk/libf/phylmd/cosp/mod_cosp_stats.F90

    r4593 r4619  
    3636!
    3737!
    38 INCLUDE "cosp_defs.h"
     38#include "cosp_defs.h"
    3939MODULE MOD_COSP_STATS
    4040  USE MOD_COSP_CONSTANTS
  • LMDZ6/trunk/libf/phylmd/cosp/phys_cosp.F90

    r4593 r4619  
    7373
    7474!! AI rajouter
    75   INCLUDE "cosp_defs.h"
     75#include "cosp_defs.h"
    7676  USE MOD_COSP_CONSTANTS
    7777  USE MOD_COSP_TYPES
     
    8484  use cosp_output_write_mod
    8585!  use MOD_COSP_Modis_Simulator, only : cosp_modis
    86 #ifdef CPP_XIOS
    87     USE xios, ONLY: xios_field_is_active
    88 #endif
     86  USE lmdz_xios, ONLY: xios_field_is_active, using_xios
    8987  use cosp_read_otputkeys
    9088
     
    183181
    184182! Clefs Outputs initialisation
    185 #ifdef CPP_XIOS
    186   call cosp_outputkeys_init(cfg)
    187 #else
    188   call read_cosp_output_nl(itap,cosp_output_nl,cfg)
    189 #endif
     183  IF (using_xios) THEN
     184    call cosp_outputkeys_init(cfg)
     185  ELSE
     186    call read_cosp_output_nl(itap,cosp_output_nl,cfg)
     187  ENDIF
     188
    190189!!!   call cosp_outputkeys_test(cfg)
    191190  print*,' Cles des differents simulateurs cosp a itap :',itap
     
    203202!!! Ici on modifie les cles logiques pour les outputs selon les champs actives dans les .xml
    204203  if ((itap.gt.1).and.(first_write))then
    205 #ifdef CPP_XIOS
    206     call read_xiosfieldactive(cfg)
    207 #endif
     204   
     205    IF (using_xios) call read_xiosfieldactive(cfg)
     206 
    208207    first_write=.false.
    209208
  • LMDZ6/trunk/libf/phylmd/cosp2/cosp_interface_v1p4.F90

    r4593 r4619  
    3030! May 2015 - D. Swales - Original version
    3131! %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    32 INCLUDE "cosp_defs.h"
     32#include "cosp_defs.h"
    3333MODULE MOD_COSP_INTERFACE_v1p4
    3434  use COSP_KINDS,          only: wp,dp
  • LMDZ6/trunk/libf/phylmd/cosp2/cosp_output_mod.F90

    r3435 r4619  
    246246  USE time_phylmdz_mod, ONLY: day_ref, annee_ref, day_ini, start_time, itau_phy
    247247  USE print_control_mod, ONLY: lunout
    248 
    249 #ifdef CPP_XIOS
    250248    ! ug Pour les sorties XIOS
    251     USE wxios
    252 #endif
     249  USE wxios
    253250
    254251  IMPLICIT NONE
     
    275272!!! Variables d'entree
    276273
    277 #ifdef CPP_XIOS
    278     ! ug Variables utilisées pour récupérer le calendrier pour xios
    279     INTEGER :: x_an, x_mois, x_jour
    280     REAL :: x_heure
    281     INTEGER :: ini_an, ini_mois, ini_jour
    282     REAL :: ini_heure
    283 #endif
     274! ug Variables utilisées pour récupérer le calendrier pour xios
     275  INTEGER :: x_an, x_mois, x_jour
     276  REAL :: x_heure
     277  INTEGER :: ini_an, ini_mois, ini_jour
     278  REAL :: ini_heure
    284279
    285280    WRITE(lunout,*) 'Debut cosp_output_mod.F90'
     
    328323    CALL ymds2ju(annee_ref, 1, day_ini, start_time, zjulian_start)
    329324
    330 #ifdef CPP_XIOS
    331    
    332 ! recuperer la valeur indefine Xios
    333 !    CALL xios_get_field_attr("clcalipso",default_value=Cosp_fill_value)
    334 !         Cosp_fill_value=missing_val
    335           Cosp_fill_value=0.
    336          print*,'Cosp_fill_value=',Cosp_fill_value
    337 
    338     CALL wxios_add_vaxis("height", vgrid%Nlvgrid, vgrid%z)
    339     print*,'wxios_add_vaxis vgrid%Nlvgrid, vgrid%z',vgrid%Nlvgrid,vgrid%z
    340 
    341     WRITE(lunout,*) 'wxios_add_vaxis height_mlev, Nlevlmdz vgrid%mz ', &
     325    IF (using_xios) THEN
     326
     327  ! recuperer la valeur indefine Xios
     328  !    CALL xios_get_field_attr("clcalipso",default_value=Cosp_fill_value)
     329  !         Cosp_fill_value=missing_val
     330      Cosp_fill_value=0.
     331      print*,'Cosp_fill_value=',Cosp_fill_value
     332
     333      CALL wxios_add_vaxis("height", vgrid%Nlvgrid, vgrid%z)
     334      print*,'wxios_add_vaxis vgrid%Nlvgrid, vgrid%z',vgrid%Nlvgrid,vgrid%z
     335
     336      WRITE(lunout,*) 'wxios_add_vaxis height_mlev, Nlevlmdz vgrid%mz ', &
    342337                     Nlevlmdz,vgrid%mz
    343     CALL wxios_add_vaxis("height_mlev", Nlevlmdz, vgrid%mz)
    344 
    345     WRITE(lunout,*) 'wxios_add_vaxis sza, PARASOL_NREFL ', &
    346                      PARASOL_NREFL, PARASOL_SZA
    347     CALL wxios_add_vaxis("sza", PARASOL_NREFL, PARASOL_SZA)
    348 
    349     WRITE(lunout,*) 'wxios_add_vaxis pressure2 ',7,pres_binCenters
    350     CALL wxios_add_vaxis("pressure2", 7, pres_binCenters)
    351 
    352     WRITE(lunout,*) 'wxios_add_vaxis column ',Ncolumns,column_ax
    353     CALL wxios_add_vaxis("column", Ncolumns, column_ax)
    354 
    355    WRITE(lunout,*) 'wxios_add_vaxis temp LIDAR_NTEMP, LIDAR_PHASE_TEMP ', &
     338      CALL wxios_add_vaxis("height_mlev", Nlevlmdz, vgrid%mz)
     339
     340      WRITE(lunout,*) 'wxios_add_vaxis sza, PARASOL_NREFL ', &
     341                       PARASOL_NREFL, PARASOL_SZA
     342      CALL wxios_add_vaxis("sza", PARASOL_NREFL, PARASOL_SZA)
     343
     344      WRITE(lunout,*) 'wxios_add_vaxis pressure2 ',7,pres_binCenters
     345      CALL wxios_add_vaxis("pressure2", 7, pres_binCenters)
     346
     347      WRITE(lunout,*) 'wxios_add_vaxis column ',Ncolumns,column_ax
     348      CALL wxios_add_vaxis("column", Ncolumns, column_ax)
     349
     350      WRITE(lunout,*) 'wxios_add_vaxis temp LIDAR_NTEMP, LIDAR_PHASE_TEMP ', &
    356351                    LIDAR_NTEMP, LIDAR_PHASE_TEMP
    357    CALL wxios_add_vaxis("temp", LIDAR_NTEMP, LIDAR_PHASE_TEMP)
    358 
    359    WRITE(lunout,*) 'wxios_add_vaxis cth16 numMISRHgtBins, misr_histHgtCenters ', &
    360                     numMISRHgtBins, misr_histHgtCenters
    361    CALL wxios_add_vaxis("cth16", numMISRHgtBins, misr_histHgtCenters)
    362 
    363    WRITE(lunout,*) 'wxios_add_vaxis dbze DBZE_BINS, dbze_ax ', &
    364                     DBZE_BINS, dbze_ax
    365    CALL wxios_add_vaxis("dbze", DBZE_BINS, dbze_ax)
    366 
    367    WRITE(lunout,*) 'wxios_add_vaxis scatratio SR_BINS, sratio_ax', &
    368                    SR_BINS, sratio_ax
    369    CALL wxios_add_vaxis("scatratio", SR_BINS, sratio_ax)
    370 
    371    WRITE(lunout,*) 'wxios_add_vaxis ReffIce numMODISReffIceBins, &
    372                    reffICE_binCenters',numMODISReffIceBins, reffICE_binCenters
    373    CALL wxios_add_vaxis("ReffIce", numMODISReffIceBins, reffICE_binCenters)
    374 
    375    WRITE(lunout,*) 'wxios_add_vaxis ReffLiq numMODISReffLiqBins, &
     352      CALL wxios_add_vaxis("temp", LIDAR_NTEMP, LIDAR_PHASE_TEMP)
     353
     354      WRITE(lunout,*) 'wxios_add_vaxis cth16 numMISRHgtBins, misr_histHgtCenters ', &
     355                      numMISRHgtBins, misr_histHgtCenters
     356      CALL wxios_add_vaxis("cth16", numMISRHgtBins, misr_histHgtCenters)
     357
     358      WRITE(lunout,*) 'wxios_add_vaxis dbze DBZE_BINS, dbze_ax ', &
     359                       DBZE_BINS, dbze_ax
     360      CALL wxios_add_vaxis("dbze", DBZE_BINS, dbze_ax)
     361
     362      WRITE(lunout,*) 'wxios_add_vaxis scatratio SR_BINS, sratio_ax', &
     363                     SR_BINS, sratio_ax
     364      CALL wxios_add_vaxis("scatratio", SR_BINS, sratio_ax)
     365
     366      WRITE(lunout,*) 'wxios_add_vaxis ReffIce numMODISReffIceBins, &
     367                     reffICE_binCenters',numMODISReffIceBins, reffICE_binCenters
     368     CALL wxios_add_vaxis("ReffIce", numMODISReffIceBins, reffICE_binCenters)
     369
     370     WRITE(lunout,*) 'wxios_add_vaxis ReffLiq numMODISReffLiqBins, &
    376371                    reffLIQ_binCenters', numMODISReffLiqBins, reffLIQ_binCenters
    377    CALL wxios_add_vaxis("ReffLiq", numMODISReffLiqBins, reffLIQ_binCenters)
    378 
    379    WRITE(lunout,*) 'wxios_add_vaxis 7, tau_binCenters', &
    380                     7, tau_binCenters
    381    CALL wxios_add_vaxis("tau", 7, tau_binCenters)
    382 
    383 #endif
    384    
     372     CALL wxios_add_vaxis("ReffLiq", numMODISReffLiqBins, reffLIQ_binCenters)
     373
     374     WRITE(lunout,*) 'wxios_add_vaxis 7, tau_binCenters', &
     375                      7, tau_binCenters
     376     CALL wxios_add_vaxis("tau", 7, tau_binCenters)
     377
     378  ENDIF
     379
    385380    zdtimemoy_cosp = freq_COSP         ! Frequence ou l on moyenne
    386381
     
    394389!                    nhoricosp(iff),cosp_nidfiles(iff)
    395390
    396 #ifdef CPP_XIOS
    397         IF (.not. ok_all_xml) then
    398          WRITE(lunout,*) 'wxios_add_file ',cosp_outfilenames(iff)
    399          CALL wxios_add_file(cosp_outfilenames(iff),chfreq(iff),10)
     391        IF(using_xios) THEN
     392          IF (.not. ok_all_xml) then
     393           WRITE(lunout,*) 'wxios_add_file ',cosp_outfilenames(iff)
     394           CALL wxios_add_file(cosp_outfilenames(iff),chfreq(iff),10)
     395          ENDIF
    400396        ENDIF
    401 #endif
    402397
    403398#ifndef CPP_IOIPSL_NO_OUTPUT
  • LMDZ6/trunk/libf/phylmd/cosp2/cosp_output_write_mod.F90

    r3398 r4619  
    3636    USE time_phylmdz_mod, ONLY: itau_phy, start_time, day_step_phy
    3737    USE print_control_mod, ONLY: lunout,prt_level
    38 
    39 #ifdef CPP_XIOS
    4038    USE wxios, only: wxios_closedef
    41     USE xios, only: xios_update_calendar, xios_field_is_active
    42 #endif
     39    USE lmdz_xios, only: xios_update_calendar, xios_field_is_active, using_xios
    4340  IMPLICIT NONE 
    4441!!! Variables d'entree
     
    6865  real, dimension(Npoints,numMISRHgtBins,7) :: tmp_fi4da_misr
    6966
    70 #ifdef CPP_XIOS
    71   missing_val=missing_cosp
    72 #else
    73   missing_val=0.
    74 #endif
     67  IF (using_xios) THEN
     68    missing_val=missing_cosp
     69  ELSE
     70    missing_val=0.
     71  ENDIF
    7572
    7673  Nlevout = vgrid%Nlvgrid
     
    10097!   endif
    10198
    102 !!#ifdef CPP_XIOS
     99!! IF (using_xios) THEN
    103100! !$OMP MASTER
    104101!IF (cosp_varsdefined) THEN
     
    111108!  !$OMP END MASTER
    112109!  !$OMP BARRIER
    113 !!#endif
     110!! ENDIF
    114111
    115112!!!! Sorties Calipso
     
    173170!   if (cfg%Lproftemp) CALL histwrite3d_cosp(o_proftemp,stlidar%proftemp,nvert)                    !TIBO
    174171
    175 #ifdef CPP_XIOS
    176    do icl=1,SR_BINS
     172  IF (using_xios) THEN
     173
     174    do icl=1,SR_BINS
    177175      tmp_fi4da_cfadL(:,:,icl)=stlidar%cfad_sr(:,icl,:)
    178    enddo
     176    enddo
    179177!   if (cfg%LcfadLidarsr532) CALL histwrite4d_cosp(o_cfad_lidarsr532,stlidar%cfad_sr)
    180    if (cfg%LcfadLidarsr532) CALL histwrite4d_cosp(o_cfad_lidarsr532,tmp_fi4da_cfadL)
     178    if (cfg%LcfadLidarsr532) CALL histwrite4d_cosp(o_cfad_lidarsr532,tmp_fi4da_cfadL)
    181179!   if (cfg%LprofSR) CALL histwrite4d_cosp(o_profSR,stlidar%profSR)                              !TIBO
    182 #else
    183    if (cfg%LcfadLidarsr532) then
    184      do icl=1,SR_BINS
     180  ELSE
     181    if (cfg%LcfadLidarsr532) then
     182      do icl=1,SR_BINS
    185183        CALL histwrite3d_cosp(o_cfad_lidarsr532,stlidar%cfad_sr(:,icl,:),nvert,icl)
    186      enddo
    187    endif
     184      enddo
     185    endif
    188186!   if (cfg%LprofSR) then
    189187!     do icl=1,Ncolumns                                                              !TIBO
     
    191189!     enddo                                                                          !TIBO
    192190!   endif
    193 #endif
     191  ENDIF
     192
    194193   if (cfg%LparasolRefl) CALL histwrite3d_cosp(o_parasol_refl,stlidar%parasolrefl,nvertp)
    195194
     
    211210  endif
    212211
    213 #ifdef CPP_XIOS
    214    if (cfg%Latb532) CALL histwrite4d_cosp(o_atb532,sglidar%beta_tot)
    215 #else
    216    if (cfg%Latb532) then 
    217      do icl=1,Ncolumns
     212  IF (using_xios) THEN
     213
     214    if (cfg%Latb532) CALL histwrite4d_cosp(o_atb532,sglidar%beta_tot)
     215  ELSE
     216    if (cfg%Latb532) then 
     217      do icl=1,Ncolumns
    218218        CALL histwrite3d_cosp(o_atb532,sglidar%beta_tot(:,icl,:),nvertmcosp,icl)
    219      enddo
    220    endif
    221 #endif
     219      enddo
     220    endif
     221  ENDIF
    222222
    223223   if (cfg%LlidarBetaMol532) CALL histwrite3d_cosp(o_beta_mol532,sglidar%beta_mol,nvertmcosp)
     
    229229
    230230   where(stradar%cfad_ze == R_UNDEF) stradar%cfad_ze = missing_val
    231 #ifdef CPP_XIOS
    232    do icl=1,DBZE_BINS
    233      tmp_fi4da_cfadR(:,:,icl)=stradar%cfad_ze(:,icl,:)
    234    enddo
    235    if (cfg%Ldbze94) CALL histwrite4d_cosp(o_dbze94,sgradar%Ze_tot)
    236 !   if (cfg%LcfadDbze94) CALL histwrite4d_cosp(o_cfadDbze94,stradar%cfad_ze)
    237    if (cfg%LcfadDbze94) CALL histwrite4d_cosp(o_cfadDbze94,tmp_fi4da_cfadR)
    238 #else
    239    if (cfg%Ldbze94) then
    240     do icl=1,Ncolumns
    241        CALL histwrite3d_cosp(o_dbze94,sgradar%Ze_tot(:,icl,:),nvert,icl)
     231  IF (using_xios) THEN
     232    do icl=1,DBZE_BINS
     233      tmp_fi4da_cfadR(:,:,icl)=stradar%cfad_ze(:,icl,:)
    242234    enddo
    243    endif
    244    if (cfg%LcfadDbze94) then
    245     do icl=1,DBZE_BINS
    246     CALL histwrite3d_cosp(o_cfadDbze94,stradar%cfad_ze(:,icl,:),nvert,icl)
    247     enddo
    248    endif
    249 #endif
     235    if (cfg%Ldbze94) CALL histwrite4d_cosp(o_dbze94,sgradar%Ze_tot)
     236 !   if (cfg%LcfadDbze94) CALL histwrite4d_cosp(o_cfadDbze94,stradar%cfad_ze)
     237    if (cfg%LcfadDbze94) CALL histwrite4d_cosp(o_cfadDbze94,tmp_fi4da_cfadR)
     238  ELSE
     239    if (cfg%Ldbze94) then
     240      do icl=1,Ncolumns
     241        CALL histwrite3d_cosp(o_dbze94,sgradar%Ze_tot(:,icl,:),nvert,icl)
     242      enddo
     243     endif
     244     if (cfg%LcfadDbze94) then
     245       do icl=1,DBZE_BINS
     246         CALL histwrite3d_cosp(o_cfadDbze94,stradar%cfad_ze(:,icl,:),nvert,icl)
     247       enddo
     248     endif
     249  ENDIF
    250250 endif
    251251! endif pour radar
     
    273273  where(isccp%boxptop == R_UNDEF) isccp%boxptop = missing_val
    274274
    275    CALL histwrite2d_cosp(o_sunlit,gbx%sunlit)
    276 #ifdef CPP_XIOS
    277   if (cfg%Lclisccp) CALL histwrite4d_cosp(o_clisccp2,isccp%fq_isccp)
    278 #else
    279    if (cfg%Lclisccp) then
    280      do icl=1,7
    281        CALL histwrite3d_cosp(o_clisccp2,isccp%fq_isccp(:,icl,:),nvertisccp,icl)
    282      enddo
    283    endif
    284 #endif
     275  CALL histwrite2d_cosp(o_sunlit,gbx%sunlit)
     276  IF (using_xios) THEN
     277    if (cfg%Lclisccp) CALL histwrite4d_cosp(o_clisccp2,isccp%fq_isccp)
     278  ELSE
     279    if (cfg%Lclisccp) then
     280      do icl=1,7
     281        CALL histwrite3d_cosp(o_clisccp2,isccp%fq_isccp(:,icl,:),nvertisccp,icl)
     282      enddo
     283    endif
     284  ENDIF
    285285
    286286   if (cfg%Lboxtauisccp) CALL histwrite3d_cosp(o_boxtauisccp,isccp%boxtau,nvertcol)
     
    298298   where(misr%fq_MISR == R_UNDEF) misr%fq_MISR = missing_val
    299299
    300 #ifdef CPP_XIOS
    301    do icl=1,numMISRHgtBins
     300  IF (using_xios) THEN
     301    do icl=1,numMISRHgtBins
    302302      tmp_fi4da_misr(:,icl,:)=misr%fq_MISR(:,:,icl)
    303    enddo
     303    enddo
    304304!   if (cfg%LclMISR) CALL histwrite4d_cosp(o_clMISR,misr%fq_MISR)
    305    if (cfg%LclMISR) CALL histwrite4d_cosp(o_clMISR,tmp_fi4da_misr)
    306 #else
    307    if (cfg%LclMISR) then
    308     do icl=1,7
    309       CALL histwrite3d_cosp(o_clMISR,misr%fq_MISR(:,icl,:),nvertmisr,icl)
    310     enddo
    311    endif
    312 #endif
     305    if (cfg%LclMISR) CALL histwrite4d_cosp(o_clMISR,tmp_fi4da_misr)
     306  ELSE
     307    if (cfg%LclMISR) then
     308      do icl=1,7
     309        CALL histwrite3d_cosp(o_clMISR,misr%fq_MISR(:,icl,:),nvertmisr,icl)
     310      enddo
     311     endif
     312  ENDIF
    313313 endif
    314314! endif pour Misr
     
    375375          modis%Optical_Thickness_vs_Cloud_Top_Pressure = missing_val
    376376
    377 #ifdef CPP_XIOS
    378    if (cfg%Lclmodis) CALL histwrite4d_cosp(o_clmodis,modis%Optical_Thickness_vs_Cloud_Top_Pressure)
    379 #else
    380   if (cfg%Lclmodis) then
    381    do icl=1,7
    382    CALL histwrite3d_cosp(o_clmodis, &
    383      modis%Optical_Thickness_vs_Cloud_Top_Pressure(:,icl,:),nvertisccp,icl)           
    384    enddo
    385   endif
    386 #endif
     377  IF (using_xios) THEN
     378    if (cfg%Lclmodis) CALL histwrite4d_cosp(o_clmodis,modis%Optical_Thickness_vs_Cloud_Top_Pressure)
     379  ELSE
     380    if (cfg%Lclmodis) then
     381     do icl=1,7
     382       CALL histwrite3d_cosp(o_clmodis, &
     383         modis%Optical_Thickness_vs_Cloud_Top_Pressure(:,icl,:),nvertisccp,icl)           
     384     enddo
     385    endif
     386  ENDIF
    387387
    388388    where(modis%Optical_Thickness_vs_ReffIce == R_UNDEF) &
     
    392392          modis%Optical_Thickness_vs_ReffLiq = missing_val
    393393
    394 #ifdef CPP_XIOS
    395   if (cfg%Lclmodis) CALL histwrite4d_cosp(o_crimodis,modis%Optical_Thickness_vs_ReffIce)
    396   if (cfg%Lclmodis) CALL histwrite4d_cosp(o_crlmodis,modis%Optical_Thickness_vs_ReffLiq)
    397 #else
    398   if (cfg%Lclmodis) then
    399     do icl=1,7
    400      CALL histwrite3d_cosp(o_crimodis, &
    401           modis%Optical_Thickness_vs_ReffIce(:,icl,:),nvertReffIce,icl)
    402     enddo
    403   endif
    404   if (cfg%Lclmodis) then
    405     do icl=1,7
    406      CALL histwrite3d_cosp(o_crlmodis, &
    407           modis%Optical_Thickness_vs_ReffLiq(:,icl,:),nvertReffLiq,icl)
    408     enddo
    409   endif
    410 #endif
     394    IF (using_xios) THEN
     395      if (cfg%Lclmodis) CALL histwrite4d_cosp(o_crimodis,modis%Optical_Thickness_vs_ReffIce)
     396      if (cfg%Lclmodis) CALL histwrite4d_cosp(o_crlmodis,modis%Optical_Thickness_vs_ReffLiq)
     397    ELSE
     398      if (cfg%Lclmodis) then
     399        do icl=1,7
     400          CALL histwrite3d_cosp(o_crimodis, &
     401             modis%Optical_Thickness_vs_ReffIce(:,icl,:),nvertReffIce,icl)
     402        enddo
     403      endif
     404      if (cfg%Lclmodis) then
     405        do icl=1,7
     406           CALL histwrite3d_cosp(o_crlmodis, &
     407              modis%Optical_Thickness_vs_ReffLiq(:,icl,:),nvertReffLiq,icl)
     408        enddo
     409      endif
     410  ENDIF !using_xios
    411411 endif !modis
    412412
     
    421421#endif
    422422! Fermeture dans phys_output_write
    423 !#ifdef CPP_XIOS
     423! IF (using_xios) THEN
    424424            !On finalise l'initialisation:
    425425            !CALL wxios_closedef()
    426 !#endif
     426! ELSE
    427427
    428428!$OMP END MASTER
     
    461461    USE mod_grid_phy_lmdz, ONLY: nbp_lon
    462462    USE print_control_mod, ONLY: lunout,prt_level
    463 #ifdef CPP_XIOS
    464   USE wxios
    465 #endif
     463    USE wxios
    466464
    467465    IMPLICIT NONE
     
    495493    ENDIF
    496494
    497 #ifdef CPP_XIOS
     495    IF (using_xios) THEN
    498496     IF (.not. ok_all_xml) then
    499497       IF ( var%cles(iff) ) THEN
     
    505503       ENDIF
    506504     ENDIF
    507 #endif
     505    ENDIF
    508506
    509507#ifndef CPP_IOIPSL_NO_OUTPUT
     
    524522    USE mod_grid_phy_lmdz, ONLY: nbp_lon
    525523    USE print_control_mod, ONLY: lunout,prt_level
    526 
    527 #ifdef CPP_XIOS
    528   USE wxios
    529 #endif
    530 
     524    USE wxios
    531525
    532526    IMPLICIT NONE
     
    601595    ENDIF
    602596
    603 #ifdef CPP_XIOS
     597    IF (using_xios) THEN
    604598      IF (.not. ok_all_xml) then
    605599        IF ( var%cles(iff) ) THEN
     
    611605        ENDIF
    612606      ENDIF
    613 #endif
     607    ENDIF
    614608
    615609#ifndef CPP_IOIPSL_NO_OUTPUT
     
    631625  USE mod_grid_phy_lmdz, ONLY: nbp_lon
    632626  USE print_control_mod, ONLY: lunout,prt_level
    633 
    634 #ifdef CPP_XIOS
    635   USE xios, only: xios_send_field
    636 #endif
     627  USE lmdz_xios, only: xios_send_field, using_xios
    637628
    638629  IMPLICIT NONE
     
    677668      firstx=.true.
    678669      DO iff=1, 3
    679            IF (var%cles(iff) .AND. cosp_outfilekeys(iff)) THEN
     670          IF (var%cles(iff) .AND. cosp_outfilekeys(iff)) THEN
    680671                ALLOCATE(index2d(nbp_lon*jj_nb))
    681672#ifndef CPP_IOIPSL_NO_OUTPUT
     
    683674#endif
    684675                deallocate(index2d)
    685 #ifdef CPP_XIOS
     676            IF (using_xios) THEN
    686677              IF (.not. ok_all_xml) then
    687678                 if (firstx) then
     
    693684                 endif
    694685              ENDIF
    695 #endif
    696            ENDIF
     686            ENDIF
     687          ENDIF
    697688      ENDDO
    698689
    699 #ifdef CPP_XIOS
     690    IF (using_xios) THEN
    700691      IF (ok_all_xml) THEN
    701692        if (prt_level >= 1) then
     
    704695       CALL xios_send_field(var%name, Field2d)
    705696      ENDIF
    706 #endif
     697    ENDIF
    707698
    708699!$OMP END MASTER   
     
    720711  USE mod_grid_phy_lmdz, ONLY: nbp_lon
    721712  USE print_control_mod, ONLY: lunout,prt_level
    722 
    723 #ifdef CPP_XIOS
    724   USE xios, only: xios_send_field
    725 #endif
    726 
     713  USE lmdz_xios, only: xios_send_field, using_xios
    727714
    728715  IMPLICIT NONE
     
    786773#endif
    787774
    788 #ifdef CPP_XIOS
     775       IF (using_xios) THEN
    789776          IF (.not. ok_all_xml) then
    790777           IF (firstx) THEN
     
    794781           ENDIF
    795782          ENDIF
    796 #endif
     783        ENDIF
    797784         deallocate(index3d)
    798785        ENDIF
    799786      ENDDO
    800 #ifdef CPP_XIOS
    801     IF (ok_all_xml) THEN
    802      CALL xios_send_field(nom, Field3d(:,:,1:nlev))
    803      IF (prt_level >= 1) WRITE(lunout,*)'xios_send_field ',var%name
     787
     788    IF (using_xios) THEN
     789      IF (ok_all_xml) THEN
     790        CALL xios_send_field(nom, Field3d(:,:,1:nlev))
     791        IF (prt_level >= 1) WRITE(lunout,*)'xios_send_field ',var%name
     792      ENDIF
    804793    ENDIF
    805 #endif
    806794
    807795!$OMP END MASTER   
     
    819807  USE mod_grid_phy_lmdz, ONLY: nbp_lon
    820808  USE print_control_mod, ONLY: lunout,prt_level
    821 
    822 #ifdef CPP_XIOS
    823   USE xios, only: xios_send_field
    824 #endif
    825 
     809  USE lmdz_xios, only: xios_send_field, using_xios
    826810
    827811  IMPLICIT NONE
     
    852836    CALL grid1Dto2D_mpi(buffer_omp,field4d)
    853837
    854 #ifdef CPP_XIOS
     838  IF (using_xios) THEN
    855839!    IF (ok_all_xml) THEN
    856840     CALL xios_send_field(var%name, Field4d(:,:,1:nlev,1:nlev2))
    857841     IF (prt_level >= 1) WRITE(lunout,*)'xios_send_field ',var%name
    858842!    ENDIF
    859 #endif
     843  ENDIF
    860844
    861845!$OMP END MASTER   
  • LMDZ6/trunk/libf/phylmd/cosp2/cosp_read_otputkeys.F90

    r3396 r4619  
    228228
    229229 SUBROUTINE READ_COSP_OUTPUT_NL(itap,cosp_nl,cfg)
    230 
    231 #ifdef CPP_XIOS
    232     USE xios, ONLY: xios_field_is_active
    233 #endif
     230  USE lmdz_xios, ONLY: xios_field_is_active, using_xios
    234231  implicit none
    235232  character(len=*),intent(in) :: cosp_nl
     
    755752!    USE MOD_COSP_CONSTANTS
    756753!    USE MOD_COSP_TYPES
    757 #ifdef CPP_XIOS
    758     USE xios, ONLY: xios_field_is_active
    759 #endif
     754     USE lmdz_xios, ONLY: xios_field_is_active, using_xios
    760755  implicit none
    761756  type(cosp_config),intent(out) :: cfg
    762757  integer :: i
    763 
    764 #ifdef CPP_XIOS
    765758
    766759 logical :: Lradar_sim,Llidar_sim,Lparasol_sim,Lisccp_sim,Lmodis_sim,Lmisr_sim,Lrttov_sim, Lstats, &
     
    784777       
    785778  character(len=32) :: out_list(78)
     779
     780 IF (using_xios) THEN
    786781
    787782  do i=1,78
     
    12491244 endif
    12501245
    1251 #endif
     1246 ENDIF !using_xios
    12521247
    12531248  END SUBROUTINE read_xiosfieldactive
  • LMDZ6/trunk/libf/phylmd/cosp2/phys_cosp2.F90

    r4593 r4619  
    8383  use cosp_output_mod
    8484  use cosp_output_write_mod
     85  USE lmdz_xios, ONLY : using_xios
    8586!  use MOD_COSP_Modis_Simulator, only : cosp_modis
    8687!  use mod_cosp_config, only : vgrid_zl,vgrid_zu,vgrid_z
     
    245246
    246247! Clefs Outputs initialisation
    247 #ifdef CPP_XIOS
     248 IF (using_xios) THEN
    248249  call cosp_outputkeys_init(cfg)
    249 #else
     250 ELSE
    250251   call read_cosp_output_nl(itap,cosp_output_nl,cfg)
    251 #endif
     252 ENDIF
    252253
    253254  print*,' Cles des differents simulateurs cosp a itap :',itap
     
    265266!!! Ici on modifie les cles logiques pour les outputs selon les champs actives dans les .xml
    266267  if ((itap.gt.1).and.(first_write))then
    267 #ifdef CPP_XIOS
    268     call read_xiosfieldactive(cfg)
    269 #endif
     268   
     269    IF (using_xios)   call read_xiosfieldactive(cfg)
    270270    first_write=.false.
    271271
  • LMDZ6/trunk/libf/phylmd/cospv2/lmdz_cosp_interface.F90

    r3723 r4619  
    6767  use ioipsl
    6868  use iophy
     69  use lmdz_xios, ONLY : using_xios
    6970  use lmdz_cosp_output_mod
    7071  use lmdz_cosp_output_write_mod
     
    262263
    263264! Clefs Outputs initialisation
    264 #ifdef CPP_XIOS
    265   call cosp_outputkeys_init(cfg)
    266 #else
     265 IF (using_xios) THEN
     266   call cosp_outputkeys_init(cfg)
     267 ELSE
    267268   call read_cosp_output_nl(itap,cosp_output_nl,cfg)
    268 #endif
     269 ENDIF
    269270
    270271  print*,' Cles des differents simulateurs cosp a itap :',itap
     
    278279    endif
    279280
    280 #ifdef CPP_XIOS
    281    print*,'On passe par ifdef CPP_XIOS'
    282 #else
    283 if (cosp_init_flag .eq. 0) then
    284 
    285     ! Initialize the distributional parameters for hydrometeors in radar simulator.
    286     ! In COSPv1.4, this was declared in cosp_defs.f.
    287     if (cloudsat_micro_scheme == 'MMF_v3.5_two_moment')  then
    288        ldouble = .true.
    289        lsingle = .false.
     281 IF (using_xios) THEN
     282   print*,'On passe par using_xios'
     283 ELSE
     284   if (cosp_init_flag .eq. 0) then
     285
     286      ! Initialize the distributional parameters for hydrometeors in radar simulator.
     287      ! In COSPv1.4, this was declared in cosp_defs.f.
     288      if (cloudsat_micro_scheme == 'MMF_v3.5_two_moment')  then
     289         ldouble = .true.
     290         lsingle = .false.
     291      endif
     292      call hydro_class_init(lsingle,ldouble,sd)
     293      call quickbeam_optics_init()
     294
     295      print*,' just before call COSP_INIT, cosp_init_flag =', cosp_init_flag
     296      call COSP_INIT(cfg%Lisccp, cfg%Lmodis, cfg%Lmisr, cfg%Lcloudsat, cfg%Lcalipso, &
     297         cfg%LgrLidar532, cfg%Latlid, cfg%Lparasol, cfg%Lrttov,          &
     298         cloudsat_radar_freq, cloudsat_k2, cloudsat_use_gas_abs,         &
     299         cloudsat_do_ray, isccp_topheight, isccp_topheight_direction,    &
     300         surface_radar, rcfg_cloudsat, use_vgrid_in, csat_vgrid_in,      &
     301         niv_sorties, Nlevels, cloudsat_micro_scheme)
     302      cosp_init_flag = 1
     303      print*,' just after call COSP_INIT, cosp_init_flag =', cosp_init_flag
    290304    endif
    291     call hydro_class_init(lsingle,ldouble,sd)
    292     call quickbeam_optics_init()
    293 
    294   print*,' just before call COSP_INIT, cosp_init_flag =', cosp_init_flag
    295   call COSP_INIT(cfg%Lisccp, cfg%Lmodis, cfg%Lmisr, cfg%Lcloudsat, cfg%Lcalipso, &
    296         cfg%LgrLidar532, cfg%Latlid, cfg%Lparasol, cfg%Lrttov,          &
    297         cloudsat_radar_freq, cloudsat_k2, cloudsat_use_gas_abs,         &
    298         cloudsat_do_ray, isccp_topheight, isccp_topheight_direction,    &
    299         surface_radar, rcfg_cloudsat, use_vgrid_in, csat_vgrid_in,      &
    300         niv_sorties, Nlevels, cloudsat_micro_scheme)
    301   cosp_init_flag = 1
    302  print*,' just after call COSP_INIT, cosp_init_flag =', cosp_init_flag
    303 endif
    304 #endif
     305  ENDIF
    305306
    306307  print*,'Fin lecture Namelists, debut_cosp =',debut_cosp
     
    311312!!! Ici on modifie les cles logiques pour les outputs selon les champs actives dans les .xml
    312313  if ((itap.ge.1).and.(first_write))then
    313 #ifdef CPP_XIOS
    314     call read_xiosfieldactive(cfg)
    315 #endif
     314    IF (using_xios) call read_xiosfieldactive(cfg)
    316315    first_write=.false.
    317316
  • LMDZ6/trunk/libf/phylmd/cospv2/lmdz_cosp_output_mod.F90

    r3491 r4619  
    326326  USE time_phylmdz_mod, ONLY: day_ref, annee_ref, day_ini, start_time, itau_phy
    327327  USE print_control_mod, ONLY: lunout
    328 
    329 #ifdef CPP_XIOS
    330     ! ug Pour les sorties XIOS
    331     USE wxios
    332 #endif
     328  ! ug Pour les sorties XIOS
     329  USE wxios
    333330
    334331  IMPLICIT NONE
     
    350347!!! Variables d'entree
    351348
    352 #ifdef CPP_XIOS
    353     ! ug Variables utilisées pour récupérer le calendrier pour xios
    354     INTEGER :: x_an, x_mois, x_jour
    355     REAL :: x_heure
    356     INTEGER :: ini_an, ini_mois, ini_jour
    357     REAL :: ini_heure
    358 #endif
     349  ! ug Variables utilisées pour récupérer le calendrier pour xios
     350  INTEGER :: x_an, x_mois, x_jour
     351  REAL :: x_heure
     352  INTEGER :: ini_an, ini_mois, ini_jour
     353  REAL :: ini_heure
    359354
    360355    WRITE(lunout,*) 'Debut lmdz_cosp_output_mod.F90'
     
    401396    CALL ymds2ju(annee_ref, 1, day_ini, start_time, zjulian_start)
    402397
    403 #ifdef CPP_XIOS
     398  IF (using_xios) THEN
     399
    404400   
    405 ! recuperer la valeur indefine Xios
    406 !    CALL xios_get_field_attr("clcalipso",default_value=Cosp_fill_value)
    407 !         Cosp_fill_value=missing_val
     401  ! recuperer la valeur indefine Xios
     402  !    CALL xios_get_field_attr("clcalipso",default_value=Cosp_fill_value)
     403  !         Cosp_fill_value=missing_val
    408404          Cosp_fill_value=0.
    409405         print*,'Cosp_fill_value=',Cosp_fill_value
     
    426422    CALL wxios_add_vaxis("column", Ncolumns, column_ax)
    427423
    428    WRITE(lunout,*) 'wxios_add_vaxis temp LIDAR_NTEMP, LIDAR_PHASE_TEMP ', &
    429                     LIDAR_NTEMP, LIDAR_PHASE_TEMP
    430    CALL wxios_add_vaxis("temp", LIDAR_NTEMP, LIDAR_PHASE_TEMP)
    431 
    432    WRITE(lunout,*) 'wxios_add_vaxis cth16 numMISRHgtBins, misr_histHgtCenters ', &
     424    WRITE(lunout,*) 'wxios_add_vaxis temp LIDAR_NTEMP, LIDAR_PHASE_TEMP ', &
     425                     LIDAR_NTEMP, LIDAR_PHASE_TEMP
     426    CALL wxios_add_vaxis("temp", LIDAR_NTEMP, LIDAR_PHASE_TEMP)
     427
     428    WRITE(lunout,*) 'wxios_add_vaxis cth16 numMISRHgtBins, misr_histHgtCenters ', &
    433429                    numMISRHgtBins, misr_histHgtCenters
    434    CALL wxios_add_vaxis("cth", numMISRHgtBins, misr_histHgtCenters)
    435 
    436    WRITE(lunout,*) 'wxios_add_vaxis dbze CLOUDSAT_DBZE_BINS, cloudsat_binCenters ', &
     430    CALL wxios_add_vaxis("cth", numMISRHgtBins, misr_histHgtCenters)
     431
     432    WRITE(lunout,*) 'wxios_add_vaxis dbze CLOUDSAT_DBZE_BINS, cloudsat_binCenters ', &
    437433                    CLOUDSAT_DBZE_BINS, cloudsat_binCenters
    438    CALL wxios_add_vaxis("dbze", CLOUDSAT_DBZE_BINS, cloudsat_binCenters)
    439 
    440    WRITE(lunout,*) 'wxios_add_vaxis scatratio SR_BINS, calipso_binCenters', &
     434    CALL wxios_add_vaxis("dbze", CLOUDSAT_DBZE_BINS, cloudsat_binCenters)
     435
     436    WRITE(lunout,*) 'wxios_add_vaxis scatratio SR_BINS, calipso_binCenters', &
    441437                   SR_BINS, calipso_binCenters
    442    CALL wxios_add_vaxis("scatratio", SR_BINS, calipso_binCenters)
    443 
    444    WRITE(lunout,*) 'wxios_add_vaxis ReffIce numMODISReffIceBins, &
     438    CALL wxios_add_vaxis("scatratio", SR_BINS, calipso_binCenters)
     439
     440    WRITE(lunout,*) 'wxios_add_vaxis ReffIce numMODISReffIceBins, &
    445441                   reffICE_binCenters',numMODISReffIceBins, reffICE_binCenters
    446    CALL wxios_add_vaxis("ReffIce", numMODISReffIceBins, reffICE_binCenters)
    447 
    448    WRITE(lunout,*) 'wxios_add_vaxis ReffLiq numMODISReffLiqBins, &
     442    CALL wxios_add_vaxis("ReffIce", numMODISReffIceBins, reffICE_binCenters)
     443
     444    WRITE(lunout,*) 'wxios_add_vaxis ReffLiq numMODISReffLiqBins, &
    449445                    reffLIQ_binCenters', numMODISReffLiqBins, reffLIQ_binCenters
    450    CALL wxios_add_vaxis("ReffLiq", numMODISReffLiqBins, reffLIQ_binCenters)
    451 
    452    WRITE(lunout,*) 'wxios_add_vaxis 7, tau_binCenters', &
     446    CALL wxios_add_vaxis("ReffLiq", numMODISReffLiqBins, reffLIQ_binCenters)
     447
     448    WRITE(lunout,*) 'wxios_add_vaxis 7, tau_binCenters', &
    453449                    7, tau_binCenters
    454    CALL wxios_add_vaxis("tau", 7, tau_binCenters)
    455 
    456 #endif
     450    CALL wxios_add_vaxis("tau", 7, tau_binCenters)
     451
     452  ENDIF
    457453   
    458454    zdtimemoy_cosp = freq_COSP         ! Frequence ou l on moyenne
     
    467463!                    nhoricosp(iff),cosp_nidfiles(iff)
    468464
    469 #ifdef CPP_XIOS
     465 IF (using_xios) THEN
    470466        IF (.not. ok_all_xml) then
    471467         WRITE(lunout,*) 'wxios_add_file ',cosp_outfilenames(iff)
    472468         CALL wxios_add_file(cosp_outfilenames(iff),chfreq(iff),10)
    473469        ENDIF
    474 #endif
     470 ENDIF
    475471
    476472#ifndef CPP_IOIPSL_NO_OUTPUT
  • LMDZ6/trunk/libf/phylmd/cospv2/lmdz_cosp_output_write_mod.F90

    r3731 r4619  
    4242
    4343    USE wxios, only: wxios_closedef
    44     USE xios, only: xios_update_calendar, xios_field_is_active
     44    USE lmdz_xios, only: xios_update_calendar, xios_field_is_active
    4545  IMPLICIT NONE 
    4646!!! Variables d'entree
     
    807807  USE print_control_mod, ONLY: lunout,prt_level
    808808
    809   USE xios, only: xios_send_field
     809  USE lmdz_xios, only: xios_send_field
    810810
    811811  IMPLICIT NONE
     
    889889  USE print_control_mod, ONLY: lunout,prt_level
    890890
    891   USE xios, only: xios_send_field
     891  USE lmdz_xios, only: xios_send_field
    892892
    893893
     
    980980  USE print_control_mod, ONLY: lunout,prt_level
    981981
    982   USE xios, only: xios_send_field
     982  USE lmdz_xios, only: xios_send_field
    983983
    984984
  • LMDZ6/trunk/libf/phylmd/cospv2/lmdz_cosp_read_outputkeys.F90

    r3491 r4619  
    422422
    423423 SUBROUTINE READ_COSP_OUTPUT_NL(itap,cosp_nl,cfg)
    424 
    425 #ifdef CPP_XIOS
    426     USE xios, ONLY: xios_field_is_active
    427 #endif
     424  USE lmdz_xios, ONLY: xios_field_is_active, using_xios
    428425  implicit none
    429426  character(len=*),intent(in) :: cosp_nl
     
    10201017
    10211018 SUBROUTINE read_xiosfieldactive(cfg)
    1022 
    1023 #ifdef CPP_XIOS
    1024     USE xios, ONLY: xios_field_is_active
    1025 #endif
     1019  USE lmdz_xios, ONLY: xios_field_is_active, using_xios
    10261020  implicit none
    10271021  type(cosp_config),intent(inout) :: cfg
    10281022  integer :: i
    1029 
    1030 #ifdef CPP_XIOS
    10311023
    10321024!COSPv2 local variables
     
    10671059       
    10681060  character(len=32) :: out_list(107)
     1061
     1062 IF (using_xios) THEN
    10691063
    10701064  do i=1,107
     
    17171711 endif
    17181712
    1719 #endif
     1713 ENDIF !using_xios
    17201714
    17211715  END SUBROUTINE read_xiosfieldactive
  • LMDZ6/trunk/libf/phylmd/create_etat0_limit_unstruct.F90

    r4600 r4619  
    1010 
    1111  SUBROUTINE init_etat0_limit_unstruct
    12 #ifdef CPP_XIOS
    13   USE xios, ONLY: xios_set_axis_attr, xios_set_fieldgroup_attr, &
     12  USE lmdz_xios, ONLY: xios_set_axis_attr, xios_set_fieldgroup_attr, &
    1413                  xios_set_filegroup_attr, xios_set_file_attr
    1514  USE mod_phys_lmdz_para, ONLY: is_omp_master
     
    4948      ENDIF 
    5049
    51 #endif
    5250  END SUBROUTINE init_etat0_limit_unstruct
    5351 
    5452  SUBROUTINE create_etat0_limit_unstruct
    55 #ifdef CPP_XIOS
    5653  USE mod_grid_phy_lmdz, ONLY: grid_type, unstructured
    5754  USE create_etat0_unstruct_mod, ONLY: create_etat0_unstruct
     
    6259  USE ioipsl_getin_p_mod, ONLY: getin_p
    6360  USE dimphy, ONLY: klon
    64   USE xios, ONLY: xios_context_finalize, xios_set_current_context, &
     61  USE lmdz_xios, ONLY: xios_context_finalize, xios_set_current_context, &
    6562                  xios_finalize
    6663  USE print_control_mod, ONLY: lunout
     
    109106      ENDIF
    110107       
    111 #endif
    112108  END SUBROUTINE create_etat0_limit_unstruct
    113109 
  • LMDZ6/trunk/libf/phylmd/create_etat0_unstruct.F90

    r4595 r4619  
    99 
    1010  SUBROUTINE init_create_etat0_unstruct
    11 #ifdef CPP_XIOS
    12   USE xios
     11  USE lmdz_xios
    1312  USE netcdf
    1413  USE mod_phys_lmdz_para
     
    3938    ENDIF
    4039
    41 #endif
    42  
    4340  END SUBROUTINE init_create_etat0_unstruct
    4441 
     
    4643  SUBROUTINE create_etat0_unstruct
    4744  USE dimphy
    48 #ifdef CPP_XIOS
    49   USE xios
     45  USE lmdz_xios
    5046  USE infotrac_phy
    5147  USE fonte_neige_mod
     
    269265    CALL phyredem( "startphy.nc" )
    270266
    271 #endif
    272267  END SUBROUTINE create_etat0_unstruct
    273268
  • LMDZ6/trunk/libf/phylmd/create_limit_unstruct.F90

    r4361 r4619  
    1010  SUBROUTINE create_limit_unstruct
    1111  USE dimphy
    12 #ifdef CPP_XIOS
    13   USE xios
     12  USE lmdz_xios
    1413  USE ioipsl,             ONLY : ioget_year_len
    1514  USE time_phylmdz_mod, ONLY : annee_ref
     
    175174      CALL xios_send_field("rug_limout", rugos_year_mpi)
    176175    ENDIF
    177 #endif
    178176  END SUBROUTINE create_limit_unstruct
    179177 
  • LMDZ6/trunk/libf/phylmd/iophy.F90

    r4260 r4619  
    1616!$OMP THREADPRIVATE(itau_iophy)
    1717
    18 #ifdef CPP_XIOS
    1918  INTERFACE histwrite_phy
    2019    MODULE PROCEDURE histwrite2d_phy,histwrite3d_phy,histwrite2d_phy_old,histwrite3d_phy_old,histwrite2d_xios,histwrite3d_xios,histwrite0d_xios
    2120  END INTERFACE
    22 #else
    23   INTERFACE histwrite_phy
    24     MODULE PROCEDURE histwrite2d_phy,histwrite3d_phy,histwrite2d_phy_old,histwrite3d_phy_old
    25   END INTERFACE
    26 #endif
    2721
    2822  INTERFACE histbeg_phy_all
     
    5246    USE ioipsl, ONLY: flio_dom_set
    5347#endif
    54 #ifdef CPP_XIOS
    55   use wxios, ONLY: wxios_domain_param, wxios_domain_param_unstructured, wxios_context_init
    56 #endif
     48  use wxios, ONLY: wxios_domain_param, wxios_domain_param_unstructured, wxios_context_init, using_xios
    5749    IMPLICIT NONE
    5850    REAL,DIMENSION(klon),INTENT(IN) :: rlon
     
    7264    INTEGER :: data_ibegin, data_iend
    7365
    74 #ifdef CPP_XIOS
    75       CALL wxios_context_init
    76 #endif
     66    if (using_xios)  CALL wxios_context_init
    7767   
    7868
    7969    IF (grid_type==unstructured) THEN
    8070   
    81 #ifdef CPP_XIOS
    8271      CALL wxios_domain_param_unstructured("dom_glo")
    83 #endif
    8472
    8573    ELSE
     
    140128                      'APPLE',phys_domain_id)
    141129#endif
    142 #ifdef CPP_XIOS
     130    IF (using_xios) THEN 
    143131      ! Set values for the mask:
    144132      IF (mpi_rank == 0) THEN
     
    163151
    164152      ! Initialize the XIOS domain coreesponding to this process:
    165 #endif
     153    ENDIF
    166154!$OMP END MASTER
    167155
    168 #ifdef CPP_XIOS   
    169         CALL wxios_domain_param("dom_glo")
    170 #endif
     156      IF (using_xios) CALL wxios_domain_param("dom_glo")
    171157     
    172158    ENDIF
     
    227213  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    228214  USE ioipsl, ONLY: histbeg
    229 #ifdef CPP_XIOS
    230   USE wxios, ONLY: wxios_add_file
    231 #endif
     215  USE wxios, ONLY: wxios_add_file, using_xios
    232216  IMPLICIT NONE
    233217  INCLUDE 'clesphys.h'
     
    251235  ENDIF
    252236
    253 #ifdef CPP_XIOS
    254   ! ug OMP en chantier...
    255   IF((.NOT. is_using_mpi) .OR. is_mpi_root) THEN
    256       ! ug Création du fichier
    257     IF (.not. ok_all_xml) THEN
    258       CALL wxios_add_file(name, ffreq, lev)
     237  IF (using_xios) THEN 
     238    ! ug OMP en chantier...
     239    IF((.NOT. is_using_mpi) .OR. is_mpi_root) THEN
     240        ! ug Création du fichier
     241      IF (.not. ok_all_xml) THEN
     242        CALL wxios_add_file(name, ffreq, lev)
     243      ENDIF
    259244    ENDIF
    260245  ENDIF
    261 #endif
    262246!$OMP END MASTER
    263247 
     
    608592    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    609593    USE aero_mod, ONLY : naero_tot, name_aero_tau
    610 #ifdef CPP_XIOS
    611     USE wxios, ONLY: wxios_add_field_to_file
    612 #endif
     594    USE wxios, ONLY: wxios_add_field_to_file, using_xios
    613595    USE print_control_mod, ONLY: prt_level,lunout
    614596    IMPLICIT NONE
     
    650632    IF(.NOT.clef_stations(iff)) THEN 
    651633
    652 #ifdef CPP_XIOS
    653       IF (.not. ok_all_xml) THEN
    654         IF ( var%flag(iff)<=lev_files(iff) ) THEN
    655           CALL wxios_add_field_to_file(var%name, 2, iff, phys_out_filenames(iff), &
    656           var%description, var%unit, var%flag(iff), typeecrit)
    657           IF (prt_level >= 10) THEN
    658             WRITE(lunout,*) 'histdef2d: call wxios_add_field_to_file var%name iff: ', &
    659                             trim(var%name),iff
     634      IF (using_xios) THEN 
     635        IF (.not. ok_all_xml) THEN
     636          IF ( var%flag(iff)<=lev_files(iff) ) THEN
     637            CALL wxios_add_field_to_file(var%name, 2, iff, phys_out_filenames(iff), &
     638            var%description, var%unit, var%flag(iff), typeecrit)
     639            IF (prt_level >= 10) THEN
     640              WRITE(lunout,*) 'histdef2d: call wxios_add_field_to_file var%name iff: ', &
     641                              trim(var%name),iff
     642            ENDIF
    660643          ENDIF
    661644        ENDIF
    662645      ENDIF
    663 #endif
    664646#ifndef CPP_IOIPSL_NO_OUTPUT
    665647
     
    725707    USE print_control_mod, ONLY: prt_level,lunout
    726708    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    727 #ifdef CPP_XIOS
    728     USE wxios, ONLY: wxios_add_field_to_file
    729 #endif
     709    USE wxios, ONLY: wxios_add_field_to_file, using_xios
    730710    USE print_control_mod, ONLY: prt_level,lunout
    731711    IMPLICIT NONE
     
    766746    IF(.NOT.clef_stations(iff)) THEN
    767747
    768 #ifdef CPP_XIOS
    769        IF (.not. ok_all_xml) THEN
    770          IF ( var%flag(iff)<=lev_files(iff) ) THEN
    771          CALL wxios_add_field_to_file(var%name, 3, iff, phys_out_filenames(iff), &
    772          var%description, var%unit, var%flag(iff), typeecrit)
    773            IF (prt_level >= 10) THEN
    774              WRITE(lunout,*) 'histdef3d: call wxios_add_field_to_file var%name iff: ', &
    775                              trim(var%name),iff
    776            ENDIF
    777          ENDIF
    778        ENDIF
    779 #endif
     748      IF (using_xios) THEN 
     749
     750        IF (.not. ok_all_xml) THEN
     751          IF ( var%flag(iff)<=lev_files(iff) ) THEN
     752          CALL wxios_add_field_to_file(var%name, 3, iff, phys_out_filenames(iff), &
     753          var%description, var%unit, var%flag(iff), typeecrit)
     754            IF (prt_level >= 10) THEN
     755              WRITE(lunout,*) 'histdef3d: call wxios_add_field_to_file var%name iff: ', &
     756                              trim(var%name),iff
     757            ENDIF
     758          ENDIF
     759        ENDIF
     760      ENDIF
    780761#ifndef CPP_IOIPSL_NO_OUTPUT
    781762
     
    974955  USE print_control_mod, ONLY: prt_level,lunout
    975956  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, grid_type, unstructured, regular_lonlat
    976 #ifdef CPP_XIOS
    977   USE xios, ONLY: xios_send_field, xios_field_is_active
    978 #endif
     957  USE lmdz_xios, ONLY: xios_send_field, xios_field_is_active, using_xios
    979958  USE print_control_mod, ONLY: lunout, prt_level
    980959
     
    10361015
    10371016  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
     1017    IF (using_xios) THEN
     1018      IF (ok_all_xml) THEN
     1019        !$omp barrier
     1020        !$omp master
     1021        is_active = xios_field_is_active(var%name, at_current_timestep_arg=.false.)
     1022        !$omp end master
     1023        !$omp barrier
     1024        IF(.not. is_active) RETURN
     1025      ENDIF
     1026    ENDIF
    10481027
    10491028    !Et sinon on.... écrit
     
    10681047
    10691048      IF (ok_all_xml) THEN
    1070 #ifdef CPP_XIOS
     1049        IF (using_xios) THEN 
    10711050          IF (prt_level >= 10) THEN
    10721051             write(lunout,*)'Dans iophy histwrite2D,var%name ', trim(var%name)                       
     
    10911070                             trim(var%name)                       
    10921071          ENDIF
    1093 #else
    1094         CALL abort_physic ('iophy','cannot have ok_all_xml = .T. without CPP_XIOS defined' ,1)
    1095 #endif
     1072        ELSE
     1073          CALL abort_physic ('iophy','cannot have ok_all_xml = .T. without CPP_XIOS defined' ,1)
     1074        ENDIF
    10961075      ELSE 
    10971076        DO iff=iff_beg, iff_end
    10981077            IF (var%flag(iff) <= lev_files(iff) .AND. clef_files(iff)) THEN
    10991078
    1100 #ifdef CPP_XIOS
    1101                IF (firstx) THEN
    1102                   IF (prt_level >= 10) THEN
    1103                      write(lunout,*)'Dans iophy histwrite2D,iff,var%name ',&
    1104                                     iff,trim(var%name)                       
    1105                      write(lunout,*)"histwrite2d_phy:.NOT.clef_stations(iff)and iff==iff_beg, call xios_send_field"
    1106                   ENDIF
    1107                   IF (grid_type==regular_lonlat) THEN
    1108                     IF (SIZE(field) == klon) then
    1109                        CALL xios_send_field(var%name, Field2d)
    1110                     ELSE
     1079              IF (using_xios) THEN
     1080                IF (firstx) THEN
     1081                   IF (prt_level >= 10) THEN
     1082                      write(lunout,*)'Dans iophy histwrite2D,iff,var%name ',&
     1083                                     iff,trim(var%name)                       
     1084                      write(lunout,*)"histwrite2d_phy:.NOT.clef_stations(iff)and iff==iff_beg, call xios_send_field"
     1085                   ENDIF
     1086                   IF (grid_type==regular_lonlat) THEN
     1087                     IF (SIZE(field) == klon) then
     1088                        CALL xios_send_field(var%name, Field2d)
     1089                     ELSE
     1090                        CALL xios_send_field(var%name, field)
     1091                     ENDIF
     1092                   ELSE IF (grid_type==unstructured) THEN
     1093                     IF (SIZE(field) == klon) then
     1094                       CALL xios_send_field(var%name, buffer_omp)
     1095                     ELSE
    11111096                       CALL xios_send_field(var%name, field)
    1112                     ENDIF
    1113                   ELSE IF (grid_type==unstructured) THEN
    1114                     IF (SIZE(field) == klon) then
    1115                       CALL xios_send_field(var%name, buffer_omp)
    1116                     ELSE
    1117                       CALL xios_send_field(var%name, field)
    1118                     ENDIF
    1119                   ENDIF
    1120 
    1121                   firstx=.false.
    1122                ENDIF
    1123 #endif
     1097                     ENDIF
     1098                   ENDIF
     1099
     1100                   firstx=.false.
     1101                ENDIF
     1102              ENDIF
    11241103
    11251104                  IF (.NOT.clef_stations(iff)) THEN
     
    11291108                        CALL histwrite(nid_files(iff),var%name,itau_iophy,Field2d,nbp_lon*jj_nb,index2d)
    11301109#endif
    1131 !#ifdef CPP_XIOS
     1110!    IF (using_xios) THEN 
    11321111!                        IF (iff == iff_beg) THEN
    11331112!                          IF (prt_level >= 10) THEN
     
    11361115!                          CALL xios_send_field(var%name, Field2d)
    11371116!                        ENDIF
    1138 !#endif
     1117!    ENDIF
    11391118                  ELSE
    11401119                        ALLOCATE(fieldok(npstn))
     
    11881167                                 nid_files, swaerofree_diag
    11891168  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, grid_type, regular_lonlat, unstructured
    1190 #ifdef CPP_XIOS
    1191   USE xios, ONLY: xios_send_field, xios_field_is_active
    1192 #endif
     1169  USE lmdz_xios, ONLY: xios_send_field, xios_field_is_active, using_xios
    11931170  USE print_control_mod, ONLY: prt_level,lunout
    11941171
     
    12361213      CALL bcast_omp(swaerofree_diag)
    12371214  ELSE
    1238 #ifdef CPP_XIOS
    1239     IF (ok_all_xml) THEN
    1240       !$omp barrier
    1241       !$omp master
    1242       is_active = xios_field_is_active(var%name, at_current_timestep_arg=.false.)
    1243       !$omp end master
    1244       !$omp barrier
    1245       IF(.not. is_active) RETURN
    1246     ENDIF
    1247 #endif
     1215    IF (using_xios) THEN 
     1216      IF (ok_all_xml) THEN
     1217        !$omp barrier
     1218        !$omp master
     1219        is_active = xios_field_is_active(var%name, at_current_timestep_arg=.false.)
     1220        !$omp end master
     1221        !$omp barrier
     1222        IF(.not. is_active) RETURN
     1223      ENDIF
     1224    ENDIF
    12481225
    12491226    !Et sinon on.... écrit
     
    12731250
    12741251    IF (ok_all_xml) THEN
    1275 #ifdef CPP_XIOS
     1252      IF (using_xios) THEN 
    12761253          IF (prt_level >= 10) THEN
    12771254             write(lunout,*)'Dans iophy histwrite3D,var%name ',&
     
    12921269        ENDIF
    12931270
    1294 #else
     1271      ELSE
    12951272        CALL abort_physic ('iophy','cannot have ok_all_xml = .T. without CPP_XIOS defined' ,1)
    1296 #endif
     1273      ENDIF
    12971274    ELSE 
    12981275
    12991276      DO iff=iff_beg, iff_end
    13001277          IF (var%flag(iff) <= lev_files(iff) .AND. clef_files(iff)) THEN
    1301 #ifdef CPP_XIOS
     1278            IF (using_xios) THEN 
    13021279              IF (firstx) THEN
    13031280                IF (prt_level >= 10) THEN
     
    13241301                firstx=.false.
    13251302              ENDIF
    1326 #endif
    1327               IF (.NOT.clef_stations(iff)) THEN
    1328                         ALLOCATE(index3d(nbp_lon*jj_nb*nlev))
    1329                         ALLOCATE(fieldok(nbp_lon*jj_nb,nlev))
     1303            ENDIF
     1304           
     1305            IF (.NOT.clef_stations(iff)) THEN
     1306                      ALLOCATE(index3d(nbp_lon*jj_nb*nlev))
     1307                      ALLOCATE(fieldok(nbp_lon*jj_nb,nlev))
    13301308
    13311309#ifndef CPP_IOIPSL_NO_OUTPUT
     
    13331311#endif
    13341312
    1335 !#ifdef CPP_XIOS
     1313!    IF (using_xios) THEN 
    13361314!                        IF (iff == 1) THEN
    13371315!                              CALL xios_send_field(var%name, Field3d(:,:,1:klev))
    13381316!                        ENDIF
    1339 !#endif
     1317!    ENDIF
    13401318!                       
    13411319              ELSE
     
    13781356
    13791357! VERSION DES HISTWRITE DEDIEES AU TOUT-XIOS-XML DEJA UTILISEE DANS PHYDEV
    1380 #ifdef CPP_XIOS
    13811358  SUBROUTINE histwrite2d_xios(field_name,field)
    13821359
     
    13861363                                jj_nb, klon_mpi, is_master
    13871364  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, grid_type, unstructured
    1388   USE xios, ONLY: xios_send_field
     1365  USE lmdz_xios, ONLY: xios_send_field
    13891366  USE print_control_mod, ONLY: prt_level,lunout
    13901367
     
    14681445                                is_sequential, klon_mpi_begin, klon_mpi_end, &
    14691446                                jj_nb, klon_mpi, is_master
    1470   USE xios, ONLY: xios_send_field
     1447  USE lmdz_xios, ONLY: xios_send_field
    14711448  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, grid_type, unstructured
    14721449  USE print_control_mod, ONLY: prt_level,lunout
     
    15511528  END SUBROUTINE histwrite3d_xios
    15521529
    1553 #ifdef CPP_XIOS
    15541530  SUBROUTINE histwrite0d_xios(field_name, field)
    1555   USE xios, ONLY: xios_send_field
     1531  USE lmdz_xios, ONLY: xios_send_field
    15561532  USE mod_phys_lmdz_para, ONLY: is_master
    15571533  USE print_control_mod, ONLY: prt_level,lunout
     
    15681544
    15691545  END SUBROUTINE histwrite0d_xios
    1570 #endif
    1571 
    1572 #endif
     1546
    15731547END MODULE iophy
  • LMDZ6/trunk/libf/phylmd/limit_read_mod.F90

    r3435 r4619  
    3636  USE surface_data
    3737  USE mod_phys_lmdz_para
    38 #ifdef CPP_XIOS
    39   USE XIOS
    40 #endif
     38  USE lmdz_xios
     39
    4140  IMPLICIT NONE
    4241    INTEGER, INTENT(IN) :: first_day
     
    4544    IF ( type_ocean /= 'couple') THEN
    4645      IF (grid_type==unstructured) THEN
    47 #ifdef CPP_XIOS
    4846        IF (is_omp_master) CALL xios_set_file_attr("limit_read",enabled=.TRUE.,record_offset=first_day)
    49 #endif
    5047      ENDIF 
    5148    ENDIF
     
    172169    USE phys_cal_mod, ONLY : calend, year_len
    173170    USE print_control_mod, ONLY: lunout, prt_level
    174 #ifdef CPP_XIOS
    175     USE XIOS, ONLY: xios_recv_field
    176 #endif
     171    USE lmdz_xios, ONLY: xios_recv_field, using_xios
    177172   
    178173    IMPLICIT NONE
     
    297292      IF (grid_type==unstructured) THEN
    298293
    299 #ifdef CPP_XIOS
    300294        IF ( type_ocean /= 'couple') THEN
    301295
     
    331325          CALL Scatter_omp(rug_mpi, rugos)
    332326       END IF
    333 #endif
    334 
    335327 
    336328     ELSE      ! grid_type==regular
  • LMDZ6/trunk/libf/phylmd/moy_undefSTD.F90

    r3435 r4619  
    88  USE phys_state_var_mod
    99#endif
    10 #ifdef CPP_XIOS
    11   USE wxios, ONLY: missing_val
    12 #endif
     10  USE wxios, ONLY: missing_val_xios => missing_val, using_xios
    1311 
    1412  USE phys_cal_mod, ONLY: mth_len
    1513  IMPLICIT NONE
    1614  include "clesphys.h"
    17 #ifndef CPP_XIOS
    1815  REAL :: missing_val
    19 #endif
    2016
    2117  ! ====================================================================
     
    5955
    6056! missing_val = nf90_fill_real
    61 #ifndef CPP_XIOS
    62       missing_val=missing_val_nf90
    63 #endif
     57  IF (using_xios) THEN
     58    missing_val = missing_val_xios
     59  ELSE
     60    missing_val=missing_val_nf90
     61  ENDIF
    6462
    6563  DO n = 1, nout
  • LMDZ6/trunk/libf/phylmd/oasis.F90

    r4596 r4619  
    117117    USE surface_data, ONLY : version_ocean
    118118    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl
    119 #ifdef CPP_XIOS
    120119    USE wxios, ONLY : wxios_context_init
    121     USE xios 
    122 #endif
     120    USE lmdz_xios 
    123121    USE print_control_mod, ONLY: lunout
    124122    USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, grid_type, unstructured, regular_lonlat
     
    393391! End definition
    394392!************************************************************************************
    395 #ifdef CPP_XIOS
    396     CALL xios_oasis_enddef()
    397 #endif
     393
     394    IF (using_xios) CALL xios_oasis_enddef()
     395
    398396    CALL prism_enddef_proto(ierror)
    399397    IF (ierror .NE. PRISM_Ok) THEN
     
    404402    ENDIF
    405403
    406 #ifdef CPP_XIOS
    407 !    CALL wxios_context_init()
    408 #endif
    409 
    410 !$OMP END MASTER
     404S!$OMP END MASTER
    411405   
    412406  END SUBROUTINE inicma
  • LMDZ6/trunk/libf/phylmd/pbl_surface_mod.F90

    r4569 r4619  
    319319    use phys_output_var_mod, only: tkt, tks, taur, sss
    320320    use blowing_snow_ini_mod, only : zeta_bs
    321 #ifdef CPP_XIOS
    322     USE wxios, ONLY: missing_val
    323 #else
    324     use netcdf, only: missing_val => nf90_fill_real
    325 #endif
     321    USE wxios, ONLY: missing_val_xios => missing_val, using_xios
     322    USE netcdf, only: missing_val_netcdf => nf90_fill_real
    326323
    327324     
     
    899896    ! compression of delta_sst, delta_sal, ds_ns, dt_ns, dter, dser,
    900897    ! dt_ds, tkt, tks, taur, sss on ocean points
    901 
     898    REAL :: missing_val
    902899!****************************************************************************************
    903900! End of declarations
    904901!****************************************************************************************
     902      IF (using_xios) THEN
     903        missing_val=missing_val_xios
     904      ELSE
     905        missing_val=missing_val_netcdf
     906      ENDIF
    905907
    906908      IF (prt_level >=10) print *,' -> pbl_surface, itap ',itap
  • LMDZ6/trunk/libf/phylmd/phyaqua_mod.F90

    r4523 r4619  
    514514    USE mod_phys_lmdz_para, ONLY: is_omp_master, klon_mpi
    515515    USE mod_phys_lmdz_transfert_para, ONLY: gather_omp
    516 #ifdef CPP_XIOS
    517     USE xios
    518 #endif
     516    USE lmdz_xios
    519517    IMPLICIT NONE
    520518
     
    536534      ! on the whole physics grid
    537535 
    538 #ifdef CPP_XIOS
    539     PRINT *, 'writelim: Ecriture du fichier limit'
    540 
    541     CALL gather_omp(phy_foce, phy_mpi)
    542     IF (is_omp_master) CALL xios_send_field('foce_limout',phy_mpi)
    543 
    544     CALL gather_omp(phy_fsic, phy_mpi)
    545     IF (is_omp_master) CALL xios_send_field('fsic_limout',phy_mpi)
     536    IF (using_xios) THEN
     537      PRINT *, 'writelim: Ecriture du fichier limit'
     538
     539      CALL gather_omp(phy_foce, phy_mpi)
     540      IF (is_omp_master) CALL xios_send_field('foce_limout',phy_mpi)
     541
     542      CALL gather_omp(phy_fsic, phy_mpi)
     543      IF (is_omp_master) CALL xios_send_field('fsic_limout',phy_mpi)
    546544     
    547     CALL gather_omp(phy_fter, phy_mpi)
    548     IF (is_omp_master) CALL xios_send_field('fter_limout',phy_mpi)
     545      CALL gather_omp(phy_fter, phy_mpi)
     546      IF (is_omp_master) CALL xios_send_field('fter_limout',phy_mpi)
    549547     
    550     CALL gather_omp(phy_flic, phy_mpi)
    551     IF (is_omp_master) CALL xios_send_field('flic_limout',phy_mpi)
    552 
    553     CALL gather_omp(phy_sst, phy_mpi)
    554     IF (is_omp_master) CALL xios_send_field('sst_limout',phy_mpi)
    555 
    556     CALL gather_omp(phy_bil, phy_mpi)
    557     IF (is_omp_master) CALL xios_send_field('bils_limout',phy_mpi)
    558 
    559     CALL gather_omp(phy_alb, phy_mpi)
    560     IF (is_omp_master) CALL xios_send_field('alb_limout',phy_mpi)
    561 
    562     CALL gather_omp(phy_rug, phy_mpi)
    563     IF (is_omp_master) CALL xios_send_field('rug_limout',phy_mpi)
    564 #endif
     548      CALL gather_omp(phy_flic, phy_mpi)
     549      IF (is_omp_master) CALL xios_send_field('flic_limout',phy_mpi)
     550
     551      CALL gather_omp(phy_sst, phy_mpi)
     552      IF (is_omp_master) CALL xios_send_field('sst_limout',phy_mpi)
     553
     554      CALL gather_omp(phy_bil, phy_mpi)
     555      IF (is_omp_master) CALL xios_send_field('bils_limout',phy_mpi)
     556
     557      CALL gather_omp(phy_alb, phy_mpi)
     558      IF (is_omp_master) CALL xios_send_field('alb_limout',phy_mpi)
     559
     560      CALL gather_omp(phy_rug, phy_mpi)
     561      IF (is_omp_master) CALL xios_send_field('rug_limout',phy_mpi)
     562    ENDIF
    565563  END SUBROUTINE writelim_unstruct
    566564
  • LMDZ6/trunk/libf/phylmd/phyetat0_mod.F90

    r4613 r4619  
    3939  USE ocean_slab_mod,   ONLY: nslay, tslab, seaice, tice, ocean_slab_init
    4040  USE time_phylmdz_mod, ONLY: init_iteration, pdtphys, itau_phy
    41 #ifdef CPP_XIOS
    42   USE wxios, ONLY: missing_val
    43 #else
    44   use netcdf, only: missing_val => nf90_fill_real
    45 #endif
     41  USE wxios, ONLY: missing_val_xios => missing_val, using_xios
     42  use netcdf, only: missing_val_netcdf => nf90_fill_real
    4643  use config_ocean_skin_m, only: activate_ocean_skin
    4744
     
    9289  REAL :: lon_startphy(klon), lat_startphy(klon)
    9390  CHARACTER(LEN=maxlen) :: tname, t(2)
    94 
     91  REAL :: missing_val
     92
     93  IF (using_xios) THEN
     94    missing_val=missing_val_xios
     95  ELSE
     96    missing_val=missing_val_netcdf
     97  ENDIF
     98 
    9599  ! FH1D
    96100  !     real iolat(jjm+1)
  • LMDZ6/trunk/libf/phylmd/phys_output_ctrlout_mod.F90

    r4593 r4619  
    20652065
    20662066#ifdef CPP_Dust
    2067       INCLUDE "Dust/spla_output_dat.h"
     2067      INCLUDE 'spla_output_dat.h'
    20682068#endif
    20692069
  • LMDZ6/trunk/libf/phylmd/phys_output_mod.F90

    r4228 r4619  
    4747    USE vertical_layers_mod, ONLY: ap,bp,preff,presnivs, aps, bps, pseudoalt, presinter
    4848    USE time_phylmdz_mod, ONLY: day_ini, itau_phy, start_time, annee_ref, day_ref
    49 #ifdef CPP_XIOS
    5049    ! ug Pour les sorties XIOS
    5150    USE wxios
    52 #endif
    5351
    5452    IMPLICIT NONE
     
    129127    REAL, DIMENSION(klev+1)   :: lev_index
    130128               
    131 #ifdef CPP_XIOS
    132129    ! ug Variables utilis\'ees pour r\'ecup\'erer le calendrier pour xios
    133130    INTEGER :: x_an, x_mois, x_jour
     
    135132    INTEGER :: ini_an, ini_mois, ini_jour
    136133    REAL :: ini_heure
    137 #endif
     134
    138135    INTEGER                         :: ISW
    139136    REAL, DIMENSION(NSW)            :: wl1_sun, wl2_sun !wavelength bounds (in um) for SW
     
    290287     ENDIF
    291288
    292 #ifdef CPP_XIOS
    293     ! ug R\'eglage du calendrier xios
    294     !Temps julian => an, mois, jour, heure
    295     CALL ju2ymds(zjulian, x_an, x_mois, x_jour, x_heure)
    296     CALL ju2ymds(zjulian_start, ini_an, ini_mois, ini_jour, ini_heure)
    297     CALL wxios_set_cal(dtime, calend, x_an, x_mois, x_jour, x_heure, ini_an, &
    298                        ini_mois, ini_jour, ini_heure )
    299 #endif
     289    IF (using_xios) THEN
     290      ! ug R\'eglage du calendrier xios
     291      !Temps julian => an, mois, jour, heure
     292      CALL ju2ymds(zjulian, x_an, x_mois, x_jour, x_heure)
     293      CALL ju2ymds(zjulian_start, ini_an, ini_mois, ini_jour, ini_heure)
     294      CALL wxios_set_cal(dtime, calend, x_an, x_mois, x_jour, x_heure, ini_an, &
     295                         ini_mois, ini_jour, ini_heure )
     296    ENDIF
    300297
    301298!!!!!!!!!!!!!!!!!!!!!!! Boucle sur les fichiers !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    330327
    331328
    332 #ifdef CPP_XIOS
    333 !!! Ouverture de chaque fichier XIOS !!!!!!!!!!!
    334     IF (.not. ok_all_xml) THEN
     329    IF (using_xios) THEN
     330      !!! Ouverture de chaque fichier XIOS !!!!!!!!!!!
     331      IF (.not. ok_all_xml) THEN
     332        IF (prt_level >= 10) THEN
     333         print*,'phys_output_open: call wxios_add_file with phys_out_filenames(iff)=',trim(phys_out_filenames(iff))   
     334        ENDIF
     335        CALL wxios_add_file(phys_out_filenames(iff),chtimestep(iff),lev_files(iff)) 
     336      ENDIF
     337
     338      !!! Declaration des axes verticaux de chaque fichier:
    335339      IF (prt_level >= 10) THEN
    336         print*,'phys_output_open: call wxios_add_file with phys_out_filenames(iff)=',trim(phys_out_filenames(iff))   
     340        print*,'phys_output_open: Declare vertical axes for each file'
    337341      ENDIF
    338       CALL wxios_add_file(phys_out_filenames(iff),chtimestep(iff),lev_files(iff)) 
    339     ENDIF
    340 
    341 !!! Declaration des axes verticaux de chaque fichier:
    342     IF (prt_level >= 10) THEN
    343       print*,'phys_output_open: Declare vertical axes for each file'
    344     ENDIF
    345 
    346    IF (iff.LE.6.OR.iff.EQ.10) THEN
    347     CALL wxios_add_vaxis("presnivs", &
    348             levmax(iff) - levmin(iff) + 1, presnivs(levmin(iff):levmax(iff)))
    349     CALL wxios_add_vaxis("presinter", &
    350             klev + 1, presinter(1:klev+1))
    351     CALL wxios_add_vaxis("Ahyb", &
    352             levmax(iff) - levmin(iff) + 1, aps(levmin(iff):levmax(iff)), positif='down', &
    353             bnds=Ahyb_bounds(levmin(iff):levmax(iff),:))
    354     CALL wxios_add_vaxis("Bhyb", &
    355             levmax(iff) - levmin(iff) + 1, bps(levmin(iff):levmax(iff)), positif='down', &
    356             bnds=Bhyb_bounds(levmin(iff):levmax(iff),:))
    357     CALL wxios_add_vaxis("klev", levmax(iff) - levmin(iff) + 1, &
    358                           lev_index(levmin(iff):levmax(iff)))
    359     CALL wxios_add_vaxis("klevp1", klev+1, &
    360                           lev_index(1:klev+1))
    361     CALL wxios_add_vaxis("bnds", 2, (/1.,2./))
    362 
    363     CALL wxios_add_vaxis("Alt", &
    364             levmax(iff) - levmin(iff) + 1, pseudoalt)
    365 
    366     ! wl1_sun/wl2_sun: minimum/maximum bound of wavelength (in um)
    367     SELECT CASE(NSW)
    368       CASE(6)
    369         wl1_sun(1:6) = [0.180, 0.250, 0.440, 0.690, 1.190, 2.380]
    370         wl2_sun(1:6) = [0.250, 0.440, 0.690, 1.190, 2.380, 4.000]
    371       CASE(2)
    372         wl1_sun(1:2) = [0.250, 0.690]
    373         wl2_sun(1:2) = [0.690, 4.000]
    374     END SELECT
    375 
    376     DO ISW=1, NSW
    377      wn1_sun(ISW)=1.e+6/wl1_sun(ISW)
    378      wn2_sun(ISW)=1.e+6/wl2_sun(ISW)
    379      spbnds_sun(ISW,1)=wn2_sun(ISW)
    380      spbnds_sun(ISW,2)=wn1_sun(ISW)
    381      spectband(ISW)=(wn1_sun(ISW)+wn2_sun(ISW))/2
    382     ENDDO
     342
     343      IF (iff.LE.6.OR.iff.EQ.10) THEN
     344        CALL wxios_add_vaxis("presnivs", &
     345              levmax(iff) - levmin(iff) + 1, presnivs(levmin(iff):levmax(iff)))
     346        CALL wxios_add_vaxis("presinter", &
     347              klev + 1, presinter(1:klev+1))
     348        CALL wxios_add_vaxis("Ahyb", &
     349              levmax(iff) - levmin(iff) + 1, aps(levmin(iff):levmax(iff)), positif='down', &
     350              bnds=Ahyb_bounds(levmin(iff):levmax(iff),:))
     351        CALL wxios_add_vaxis("Bhyb", &
     352              levmax(iff) - levmin(iff) + 1, bps(levmin(iff):levmax(iff)), positif='down', &
     353              bnds=Bhyb_bounds(levmin(iff):levmax(iff),:))
     354        CALL wxios_add_vaxis("klev", levmax(iff) - levmin(iff) + 1, &
     355                              lev_index(levmin(iff):levmax(iff)))
     356        CALL wxios_add_vaxis("klevp1", klev+1, &
     357                              lev_index(1:klev+1))
     358        CALL wxios_add_vaxis("bnds", 2, (/1.,2./))
     359 
     360        CALL wxios_add_vaxis("Alt", &
     361                levmax(iff) - levmin(iff) + 1, pseudoalt)
     362
     363        ! wl1_sun/wl2_sun: minimum/maximum bound of wavelength (in um)
     364        SELECT CASE(NSW)
     365          CASE(6)
     366            wl1_sun(1:6) = [0.180, 0.250, 0.440, 0.690, 1.190, 2.380]
     367            wl2_sun(1:6) = [0.250, 0.440, 0.690, 1.190, 2.380, 4.000]
     368          CASE(2)
     369            wl1_sun(1:2) = [0.250, 0.690]
     370            wl2_sun(1:2) = [0.690, 4.000]
     371        END SELECT
     372
     373        DO ISW=1, NSW
     374          wn1_sun(ISW)=1.e+6/wl1_sun(ISW)
     375          wn2_sun(ISW)=1.e+6/wl2_sun(ISW)
     376          spbnds_sun(ISW,1)=wn2_sun(ISW)
     377          spbnds_sun(ISW,2)=wn1_sun(ISW)
     378          spectband(ISW)=(wn1_sun(ISW)+wn2_sun(ISW))/2
     379        ENDDO
    383380!
    384381!!! ajout axe vertical spectband : solar band number
    385     CALL wxios_add_vaxis("spectband", NSW, spectband, positif='down')
    386    ELSE
    387     ! NMC files
    388     CALL wxios_add_vaxis("plev", &
    389             levmax(iff) - levmin(iff) + 1, rlevSTD(levmin(iff):levmax(iff)))
    390    ENDIF
    391 #endif
     382        CALL wxios_add_vaxis("spectband", NSW, spectband, positif='down')
     383      ELSE
     384        ! NMC files
     385        CALL wxios_add_vaxis("plev", &
     386                levmax(iff) - levmin(iff) + 1, rlevSTD(levmin(iff):levmax(iff)))
     387      ENDIF
     388    ENDIF !using_xios
    392389
    393390        IF (clef_files(iff)) THEN
  • LMDZ6/trunk/libf/phylmd/phys_output_write_mod.F90

    r4608 r4619  
    420420    USE netcdf, ONLY: nf90_fill_real
    421421    USE print_control_mod, ONLY: prt_level,lunout
    422 
    423 
    424 #ifdef CPP_XIOS
    425422    ! ug Pour les sorties XIOS
    426     USE xios
    427     USE wxios, ONLY: wxios_closedef, missing_val, wxios_set_context
    428 #endif
     423    USE lmdz_xios
     424    USE wxios, ONLY: wxios_closedef, missing_val_xios=>missing_val, wxios_set_context
    429425    USE phys_cal_mod, ONLY : mth_len
    430426
     
    484480!$OMP THREADPRIVATE(kmax_100m)
    485481    REAL :: x
    486 #ifndef CPP_XIOS
    487482    REAL :: missing_val
    488 #endif
    489483    REAL, PARAMETER :: un_jour=86400.
    490484    CHARACTER(len=12) :: nvar   
     
    513507 !   ENDIF
    514508
    515 #ifdef CPP_XIOS
    516     CALL wxios_set_context
    517 #endif
    518 
    519 #ifndef CPP_XIOS
    520     missing_val=missing_val_nf90
    521 #endif
     509    IF (using_xios) CALL wxios_set_context
     510
     511    IF (using_xios) THEN
     512      missing_val=missing_val_xios
     513    ELSE
     514      missing_val=missing_val_nf90
     515    ENDIF
    522516
    523517    IF (.NOT.vars_defined) THEN
     
    554548    DO iinit=1, iinitend
    555549!      print *,'IFF iinit=', iinit, iinitend
    556 #ifdef CPP_XIOS
    557        !$OMP MASTER
    558        IF (vars_defined) THEN
    559           IF (prt_level >= 10) then
    560              write(lunout,*)"phys_output_write: call xios_update_calendar, itau_w=",itau_w
    561           ENDIF
    562 !          CALL xios_update_calendar(itau_w)
    563           CALL xios_update_calendar(itap)
    564        ENDIF
    565        !$OMP END MASTER
    566        !$OMP BARRIER
    567 #endif
     550       IF (using_xios) THEN
     551         !$OMP MASTER
     552         IF (vars_defined) THEN
     553            IF (prt_level >= 10) then
     554               write(lunout,*)"phys_output_write: call xios_update_calendar, itau_w=",itau_w
     555            ENDIF
     556!            CALL xios_update_calendar(itau_w)
     557            CALL xios_update_calendar(itap)
     558         ENDIF
     559         !$OMP END MASTER
     560         !$OMP BARRIER
     561       ENDIF
     562
    568563       ! On procède à l'écriture ou à la définition des nombreuses variables:
    569564!!! Champs 1D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    588583       CALL histwrite_phy(o_contfracOR, pctsrf(:,is_ter))
    589584!
    590 #ifdef CPP_XIOS
    591        CALL histwrite_phy("R_ecc",R_ecc)
    592        CALL histwrite_phy("R_peri",R_peri)
    593        CALL histwrite_phy("R_incl",R_incl)
    594        CALL histwrite_phy("solaire",solaire)
    595        CALL histwrite_phy(o_Ahyb, ap)
    596        CALL histwrite_phy(o_Bhyb, bp)
    597        CALL histwrite_phy(o_Ahyb_bounds, Ahyb_bounds)
    598        CALL histwrite_phy(o_Bhyb_bounds, Bhyb_bounds)
    599        CALL histwrite_phy(o_Ahyb_mid, aps)
    600        CALL histwrite_phy(o_Bhyb_mid, bps)
    601        CALL histwrite_phy(o_Ahyb_mid_bounds, Ahyb_mid_bounds)
    602        CALL histwrite_phy(o_Bhyb_mid_bounds, Bhyb_mid_bounds)
    603        CALL histwrite_phy(o_longitude, longitude_deg)
    604        CALL histwrite_phy(o_latitude, latitude_deg)
     585       IF (using_xios) THEN
     586
     587         CALL histwrite_phy("R_ecc",R_ecc)
     588         CALL histwrite_phy("R_peri",R_peri)
     589         CALL histwrite_phy("R_incl",R_incl)
     590         CALL histwrite_phy("solaire",solaire)
     591         CALL histwrite_phy(o_Ahyb, ap)
     592         CALL histwrite_phy(o_Bhyb, bp)
     593         CALL histwrite_phy(o_Ahyb_bounds, Ahyb_bounds)
     594         CALL histwrite_phy(o_Bhyb_bounds, Bhyb_bounds)
     595         CALL histwrite_phy(o_Ahyb_mid, aps)
     596         CALL histwrite_phy(o_Bhyb_mid, bps)
     597         CALL histwrite_phy(o_Ahyb_mid_bounds, Ahyb_mid_bounds)
     598         CALL histwrite_phy(o_Bhyb_mid_bounds, Bhyb_mid_bounds)
     599         CALL histwrite_phy(o_longitude, longitude_deg)
     600         CALL histwrite_phy(o_latitude, latitude_deg)
    605601!
    606602#ifdef CPP_RRTM
    607       IF (iflag_rrtm.EQ.1) THEN
    608         DO ISW=1, NSW
    609           WRITE(ch1,'(i1)') ISW
    610 !         zx_tmp_0d=RSUN(ISW)
    611 !         CALL histwrite_phy("rsun"//ch1,zx_tmp_0d)
    612           CALL histwrite_phy("rsun"//ch1,RSUN(ISW))
    613         ENDDO
    614       ENDIF
     603        IF (iflag_rrtm.EQ.1) THEN
     604          DO ISW=1, NSW
     605            WRITE(ch1,'(i1)') ISW
     606  !         zx_tmp_0d=RSUN(ISW)
     607  !         CALL histwrite_phy("rsun"//ch1,zx_tmp_0d)
     608            CALL histwrite_phy("rsun"//ch1,RSUN(ISW))
     609          ENDDO
     610        ENDIF
    615611#endif
    616612!
    617        CALL histwrite_phy("co2_ppm",co2_ppm)
    618        CALL histwrite_phy("CH4_ppb",CH4_ppb)
    619        CALL histwrite_phy("N2O_ppb",N2O_ppb)
    620        CALL histwrite_phy("CFC11_ppt",CFC11_ppt)
    621        CALL histwrite_phy("CFC12_ppt",CFC12_ppt)
     613        CALL histwrite_phy("co2_ppm",co2_ppm)
     614        CALL histwrite_phy("CH4_ppb",CH4_ppb)
     615        CALL histwrite_phy("N2O_ppb",N2O_ppb)
     616        CALL histwrite_phy("CFC11_ppt",CFC11_ppt)
     617        CALL histwrite_phy("CFC12_ppt",CFC12_ppt)
    622618!
    623 #endif
     619      ENDIF !using_xios
    624620
    625621!!! Champs 2D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    884880
    885881! offline
    886 #ifdef CPP_XIOS
    887        IF (offline) THEN
    888 
    889           coefh_stok(:,1)      = cdragh(:)
    890           coefh_stok(:,2:klev) = coefh(:,2:klev, is_ave)
     882       IF (using_xios) THEN
     883         IF (offline) THEN
     884
     885            coefh_stok(:,1)      = cdragh(:)
     886            coefh_stok(:,2:klev) = coefh(:,2:klev, is_ave)
    891887         
    892           CALL histwrite_phy('upwd_stok', upwd)
    893           CALL histwrite_phy('t_stok', t)
    894           CALL histwrite_phy('fm_th_stok', fm_therm(:,1:klev))
    895           CALL histwrite_phy('en_th_stok', entr_therm)
    896           CALL histwrite_phy('da_stok',da )
    897           CALL histwrite_phy('mp_stok',mp )
    898           CALL histwrite_phy('dnwd_stok', dnwd)
    899           CALL histwrite_phy('wght_stok', wght_cvfd)
    900           CALL histwrite_phy('coefh_stok', coefh_stok)
    901           CALL histwrite_phy('yu1_stok', u1)
    902           CALL histwrite_phy('yv1_stok', v1)
    903 
    904           DO k=1,klev
    905              IF (k<10) THEN
    906                 WRITE(nvar,'(i1)') k
    907              ELSE IF (k<100) THEN
    908                 WRITE(nvar,'(i2)') k
    909              ELSE
    910                 WRITE(nvar,'(i3)') k
    911              END IF
    912              nvar='phi_lev'//trim(nvar)
    913              CALL histwrite_phy(nvar,phi(:,:,k))
    914           END DO
     888            CALL histwrite_phy('upwd_stok', upwd)
     889            CALL histwrite_phy('t_stok', t)
     890            CALL histwrite_phy('fm_th_stok', fm_therm(:,1:klev))
     891            CALL histwrite_phy('en_th_stok', entr_therm)
     892            CALL histwrite_phy('da_stok',da )
     893            CALL histwrite_phy('mp_stok',mp )
     894            CALL histwrite_phy('dnwd_stok', dnwd)
     895            CALL histwrite_phy('wght_stok', wght_cvfd)
     896            CALL histwrite_phy('coefh_stok', coefh_stok)
     897            CALL histwrite_phy('yu1_stok', u1)
     898            CALL histwrite_phy('yv1_stok', v1)
     899
     900            DO k=1,klev
     901               IF (k<10) THEN
     902                  WRITE(nvar,'(i1)') k
     903               ELSE IF (k<100) THEN
     904                  WRITE(nvar,'(i2)') k
     905               ELSE
     906                  WRITE(nvar,'(i3)') k
     907               END IF
     908               nvar='phi_lev'//trim(nvar)
     909               CALL histwrite_phy(nvar,phi(:,:,k))
     910            END DO
    915911         
    916        ENDIF
    917 #endif
     912         ENDIF
     913       ENDIF
    918914
    919915
     
    12911287
    12921288#ifdef CPP_IOIPSL
    1293 #ifndef CPP_XIOS
    1294   IF (.NOT.ok_all_xml) THEN
    1295        ! ATTENTION, LES ANCIENS HISTWRITE ONT ETES CONSERVES EN ATTENDANT MIEUX:
    1296        ! Champs interpolles sur des niveaux de pression
    1297        DO iff=1, nfiles
    1298           ll=0
    1299           DO k=1, nlevSTD
    1300              bb2=clevSTD(k)
    1301              IF (bb2.EQ."850".OR.bb2.EQ."700".OR. &
     1289       IF (.NOT. using_xios) THEN
     1290         IF (.NOT.ok_all_xml) THEN
     1291           ! ATTENTION, LES ANCIENS HISTWRITE ONT ETES CONSERVES EN ATTENDANT MIEUX:
     1292           ! Champs interpolles sur des niveaux de pression
     1293            DO iff=1, nfiles
     1294              ll=0
     1295              DO k=1, nlevSTD
     1296                bb2=clevSTD(k)
     1297                  IF (bb2.EQ."850".OR.bb2.EQ."700".OR. &
     1298                       bb2.EQ."500".OR.bb2.EQ."200".OR. &
     1299                       bb2.EQ."100".OR. &
     1300                       bb2.EQ."50".OR.bb2.EQ."10") THEN
     1301
     1302                      ! a refaire correctement !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     1303                      ll=ll+1
     1304                      CALL histwrite_phy(o_uSTDlevs(ll),uwriteSTD(:,k,iff), iff)
     1305                      CALL histwrite_phy(o_vSTDlevs(ll),vwriteSTD(:,k,iff), iff)
     1306                      CALL histwrite_phy(o_wSTDlevs(ll),wwriteSTD(:,k,iff), iff)
     1307                      CALL histwrite_phy(o_zSTDlevs(ll),phiwriteSTD(:,k,iff), iff)
     1308                      CALL histwrite_phy(o_qSTDlevs(ll),qwriteSTD(:,k,iff), iff)
     1309                      CALL histwrite_phy(o_tSTDlevs(ll),twriteSTD(:,k,iff), iff)
     1310
     1311                  ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR.
     1312              ENDDO
     1313            ENDDO
     1314         ENDIF
     1315       ENDIF
     1316#endif
     1317
     1318       IF (using_xios) THEN
     1319         IF (ok_all_xml) THEN
     1320           !XIOS  CALL xios_get_field_attr("u850",default_value=missing_val)
     1321!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     1322            ll=0
     1323            DO k=1, nlevSTD
     1324              bb2=clevSTD(k)
     1325              IF (bb2.EQ."850".OR.bb2.EQ."700".OR. &
    13021326                  bb2.EQ."500".OR.bb2.EQ."200".OR. &
    13031327                  bb2.EQ."100".OR. &
    13041328                  bb2.EQ."50".OR.bb2.EQ."10") THEN
    1305 
    1306                 ! a refaire correctement !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    1307                 ll=ll+1
    1308                 CALL histwrite_phy(o_uSTDlevs(ll),uwriteSTD(:,k,iff), iff)
    1309                 CALL histwrite_phy(o_vSTDlevs(ll),vwriteSTD(:,k,iff), iff)
    1310                 CALL histwrite_phy(o_wSTDlevs(ll),wwriteSTD(:,k,iff), iff)
    1311                 CALL histwrite_phy(o_zSTDlevs(ll),phiwriteSTD(:,k,iff), iff)
    1312                 CALL histwrite_phy(o_qSTDlevs(ll),qwriteSTD(:,k,iff), iff)
    1313                 CALL histwrite_phy(o_tSTDlevs(ll),twriteSTD(:,k,iff), iff)
    1314 
    1315              ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR.
    1316           ENDDO
    1317        ENDDO
    1318   ENDIF
    1319 #endif
    1320 #endif
    1321 #ifdef CPP_XIOS
    1322   IF (ok_all_xml) THEN
    1323 !XIOS  CALL xios_get_field_attr("u850",default_value=missing_val)
    1324 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    1325           ll=0
    1326           DO k=1, nlevSTD
    1327              bb2=clevSTD(k)
    1328              IF (bb2.EQ."850".OR.bb2.EQ."700".OR. &
    1329                 bb2.EQ."500".OR.bb2.EQ."200".OR. &
    1330                 bb2.EQ."100".OR. &
    1331                 bb2.EQ."50".OR.bb2.EQ."10") THEN
    1332                 ll=ll+1
    1333                 CALL histwrite_phy(o_uSTDlevs(ll),ulevSTD(:,k))
    1334                 CALL histwrite_phy(o_vSTDlevs(ll),vlevSTD(:,k))
    1335                 CALL histwrite_phy(o_wSTDlevs(ll),wlevSTD(:,k))
    1336                 CALL histwrite_phy(o_zSTDlevs(ll),philevSTD(:,k))
    1337                 CALL histwrite_phy(o_qSTDlevs(ll),qlevSTD(:,k))
    1338                 CALL histwrite_phy(o_tSTDlevs(ll),tlevSTD(:,k))
    1339              ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR.
    1340           ENDDO
    1341   ENDIF
    1342 #endif
     1329                  ll=ll+1
     1330                  CALL histwrite_phy(o_uSTDlevs(ll),ulevSTD(:,k))
     1331                  CALL histwrite_phy(o_vSTDlevs(ll),vlevSTD(:,k))
     1332                  CALL histwrite_phy(o_wSTDlevs(ll),wlevSTD(:,k))
     1333                  CALL histwrite_phy(o_zSTDlevs(ll),philevSTD(:,k))
     1334                  CALL histwrite_phy(o_qSTDlevs(ll),qlevSTD(:,k))
     1335                  CALL histwrite_phy(o_tSTDlevs(ll),tlevSTD(:,k))
     1336              ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR.
     1337            ENDDO
     1338         ENDIF
     1339       ENDIF
     1340
    13431341       IF (vars_defined) THEN
    13441342          DO i=1, klon
     
    17891787       ENDIF
    17901788
    1791 #ifdef CPP_XIOS
     1789       IF (using_xios) THEN
    17921790!solbnd begin
    17931791#ifdef CPP_RRTM
    1794       IF (iflag_rrtm.EQ.1) THEN
    1795        IF (vars_defined) THEN
    1796         DO ISW=1, NSW
    1797           zx_tmp_fi3dsp(:,ISW) = swdn(:,klevp1)*swradcorr(:)*RSUN(ISW)
    1798         ENDDO
    1799         CALL histwrite_phy(o_solbnd, zx_tmp_fi3dsp)
    1800        ENDIF
    1801       ENDIF
     1792         IF (iflag_rrtm.EQ.1) THEN
     1793           IF (vars_defined) THEN
     1794             DO ISW=1, NSW
     1795               zx_tmp_fi3dsp(:,ISW) = swdn(:,klevp1)*swradcorr(:)*RSUN(ISW)
     1796             ENDDO
     1797             CALL histwrite_phy(o_solbnd, zx_tmp_fi3dsp)
     1798           ENDIF
     1799         ENDIF
    18021800#endif
    18031801!solbnd end
    1804 #endif
     1802       ENDIF
    18051803#endif
    18061804
     
    23792377!!!!!!!!!!!! Sorties niveaux de pression NMC !!!!!!!!!!!!!!!!!!!!
    23802378#ifdef CPP_IOIPSL
    2381 #ifndef CPP_XIOS
    2382   IF (.NOT.ok_all_xml) THEN
    2383        ! ATTENTION, LES ANCIENS HISTWRITE ONT ETES CONSERVES EN ATTENDANT MIEUX:
    2384        ! Champs interpolles sur des niveaux de pression
    2385        DO iff=7, nfiles-1 !--OB: here we deal with files 7,8,9
    2386 
    2387           CALL histwrite_phy(o_tnondef,tnondef(:,:,iff-6),iff)
    2388           CALL histwrite_phy(o_ta,twriteSTD(:,:,iff-6),iff)
    2389           CALL histwrite_phy(o_zg,phiwriteSTD(:,:,iff-6),iff)
    2390           CALL histwrite_phy(o_hus,qwriteSTD(:,:,iff-6),iff)
    2391           CALL histwrite_phy(o_hur,rhwriteSTD(:,:,iff-6),iff)
    2392           CALL histwrite_phy(o_ua,uwriteSTD(:,:,iff-6),iff)
    2393           CALL histwrite_phy(o_va,vwriteSTD(:,:,iff-6),iff)
    2394           CALL histwrite_phy(o_wap,wwriteSTD(:,:,iff-6),iff)
    2395           IF (vars_defined) THEN
    2396              DO k=1, nlevSTD
    2397                 DO i=1, klon
    2398                    IF (tnondef(i,k,iff-6).NE.missing_val) THEN
    2399                       IF (freq_outNMC(iff-6).LT.0) THEN
    2400                          freq_moyNMC(iff-6)=(mth_len*un_jour)/freq_calNMC(iff-6)
    2401                       ELSE
    2402                          freq_moyNMC(iff-6)=freq_outNMC(iff-6)/freq_calNMC(iff-6)
    2403                       ENDIF
    2404                       zx_tmp_fi3d_STD(i,k) = (100.*tnondef(i,k,iff-6))/freq_moyNMC(iff-6)
    2405                    ELSE
    2406                       zx_tmp_fi3d_STD(i,k) = missing_val
    2407                    ENDIF
    2408                 ENDDO
    2409              ENDDO
    2410           ENDIF
    2411           CALL histwrite_phy(o_psbg,zx_tmp_fi3d_STD,iff)
    2412           IF (vars_defined) THEN
    2413              DO k=1, nlevSTD
    2414                 DO i=1, klon
    2415                    IF (O3sumSTD(i,k,iff-6).NE.missing_val) THEN
    2416                       zx_tmp_fi3d_STD(i,k) = O3sumSTD(i,k,iff-6) * 1.e+9
    2417                    ELSE
    2418                       zx_tmp_fi3d_STD(i,k) = missing_val
    2419                    ENDIF
    2420                 ENDDO
    2421              ENDDO !k=1, nlevSTD
    2422           ENDIF
    2423           CALL histwrite_phy(o_tro3,zx_tmp_fi3d_STD,iff)
    2424           IF (read_climoz == 2) THEN
     2379       IF (.NOT. using_xios) THEN
     2380         IF (.NOT.ok_all_xml) THEN
     2381           ! ATTENTION, LES ANCIENS HISTWRITE ONT ETES CONSERVES EN ATTENDANT MIEUX:
     2382           ! Champs interpolles sur des niveaux de pression
     2383           DO iff=7, nfiles-1 !--OB: here we deal with files 7,8,9
     2384
     2385             CALL histwrite_phy(o_tnondef,tnondef(:,:,iff-6),iff)
     2386             CALL histwrite_phy(o_ta,twriteSTD(:,:,iff-6),iff)
     2387             CALL histwrite_phy(o_zg,phiwriteSTD(:,:,iff-6),iff)
     2388             CALL histwrite_phy(o_hus,qwriteSTD(:,:,iff-6),iff)
     2389             CALL histwrite_phy(o_hur,rhwriteSTD(:,:,iff-6),iff)
     2390             CALL histwrite_phy(o_ua,uwriteSTD(:,:,iff-6),iff)
     2391             CALL histwrite_phy(o_va,vwriteSTD(:,:,iff-6),iff)
     2392             CALL histwrite_phy(o_wap,wwriteSTD(:,:,iff-6),iff)
    24252393             IF (vars_defined) THEN
    2426                 DO k=1, nlevSTD
     2394               DO k=1, nlevSTD
     2395                  DO i=1, klon
     2396                     IF (tnondef(i,k,iff-6).NE.missing_val) THEN
     2397                       IF (freq_outNMC(iff-6).LT.0) THEN
     2398                          freq_moyNMC(iff-6)=(mth_len*un_jour)/freq_calNMC(iff-6)
     2399                       ELSE
     2400                          freq_moyNMC(iff-6)=freq_outNMC(iff-6)/freq_calNMC(iff-6)
     2401                       ENDIF
     2402                       zx_tmp_fi3d_STD(i,k) = (100.*tnondef(i,k,iff-6))/freq_moyNMC(iff-6)
     2403                     ELSE
     2404                       zx_tmp_fi3d_STD(i,k) = missing_val
     2405                     ENDIF
     2406                  ENDDO
     2407               ENDDO
     2408             ENDIF
     2409             CALL histwrite_phy(o_psbg,zx_tmp_fi3d_STD,iff)
     2410             IF (vars_defined) THEN
     2411               DO k=1, nlevSTD
     2412                  DO i=1, klon
     2413                    IF (O3sumSTD(i,k,iff-6).NE.missing_val) THEN
     2414                       zx_tmp_fi3d_STD(i,k) = O3sumSTD(i,k,iff-6) * 1.e+9
     2415                    ELSE
     2416                       zx_tmp_fi3d_STD(i,k) = missing_val
     2417                    ENDIF
     2418                  ENDDO
     2419               ENDDO !k=1, nlevSTD
     2420             ENDIF
     2421             CALL histwrite_phy(o_tro3,zx_tmp_fi3d_STD,iff)
     2422             IF (read_climoz == 2) THEN
     2423               IF (vars_defined) THEN
     2424                 DO k=1, nlevSTD
    24272425                   DO i=1, klon
    24282426                      IF (O3daysumSTD(i,k,iff-6).NE.missing_val) THEN
     
    24322430                      ENDIF
    24332431                   ENDDO
    2434                 ENDDO !k=1, nlevSTD
     2432                 ENDDO !k=1, nlevSTD
     2433               ENDIF
     2434               CALL histwrite_phy(o_tro3_daylight,zx_tmp_fi3d_STD,iff)
    24352435             ENDIF
    2436              CALL histwrite_phy(o_tro3_daylight,zx_tmp_fi3d_STD,iff)
    2437           endif
    2438           CALL histwrite_phy(o_uxv,uvsumSTD(:,:,iff-6),iff)
    2439           CALL histwrite_phy(o_vxq,vqsumSTD(:,:,iff-6),iff)
    2440           CALL histwrite_phy(o_vxT,vTsumSTD(:,:,iff-6),iff)
    2441           CALL histwrite_phy(o_wxq,wqsumSTD(:,:,iff-6),iff)
    2442           CALL histwrite_phy(o_vxphi,vphisumSTD(:,:,iff-6),iff)
    2443           CALL histwrite_phy(o_wxT,wTsumSTD(:,:,iff-6),iff)
    2444           CALL histwrite_phy(o_uxu,u2sumSTD(:,:,iff-6),iff)
    2445           CALL histwrite_phy(o_vxv,v2sumSTD(:,:,iff-6),iff)
    2446           CALL histwrite_phy(o_TxT,T2sumSTD(:,:,iff-6),iff)
    2447        ENDDO !nfiles
    2448   ENDIF
     2436             CALL histwrite_phy(o_uxv,uvsumSTD(:,:,iff-6),iff)
     2437             CALL histwrite_phy(o_vxq,vqsumSTD(:,:,iff-6),iff)
     2438             CALL histwrite_phy(o_vxT,vTsumSTD(:,:,iff-6),iff)
     2439             CALL histwrite_phy(o_wxq,wqsumSTD(:,:,iff-6),iff)
     2440             CALL histwrite_phy(o_vxphi,vphisumSTD(:,:,iff-6),iff)
     2441             CALL histwrite_phy(o_wxT,wTsumSTD(:,:,iff-6),iff)
     2442             CALL histwrite_phy(o_uxu,u2sumSTD(:,:,iff-6),iff)
     2443             CALL histwrite_phy(o_vxv,v2sumSTD(:,:,iff-6),iff)
     2444             CALL histwrite_phy(o_TxT,T2sumSTD(:,:,iff-6),iff)
     2445           ENDDO !nfiles
     2446         ENDIF
     2447       ENDIF !.NOT. using_xios
    24492448#endif
    2450 #endif
    2451 #ifdef CPP_XIOS
    2452   IF (ok_all_xml) THEN
    2453 !      DO iff=7, nfiles
     2449
     2450       IF (using_xios) THEN
     2451         IF (ok_all_xml) THEN
     2452    !      DO iff=7, nfiles
    24542453
    24552454!         CALL histwrite_phy(o_tnondef,tnondef(:,:,3))
     
    25142513          CALL histwrite_phy(o_TxT,T2STD(:,:))
    25152514!      ENDDO !nfiles
    2516   ENDIF
    2517 #endif
     2515    ENDIF
     2516  ENDIF !using_xios
    25182517!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    25192518       IF (iflag_phytrac == 1 ) then
     
    26982697          ENDDO !  iff
    26992698#endif
    2700 #ifdef CPP_XIOS
    27012699          !On finalise l'initialisation:
    2702           CALL wxios_closedef()
    2703 #endif
     2700          IF (using_xios) CALL wxios_closedef()
     2701
    27042702          !$OMP END MASTER
    27052703          !$OMP BARRIER
  • LMDZ6/trunk/libf/phylmd/physiq_mod.F90

    r4613 r4619  
    7676    USE vampir
    7777    USE write_field_phy
    78 #ifdef CPP_XIOS
    7978    USE wxios, ONLY: g_ctx, wxios_set_context
    80 #endif
    8179    USE lscp_mod, ONLY : lscp
    8280    USE lmdz_wake_ini, ONLY : wake_ini
     
    134132#endif
    135133
    136 
    137 #ifdef CPP_XIOS
    138     USE xios, ONLY: xios_update_calendar, xios_context_finalize
    139     USE xios, ONLY: xios_get_field_attr, xios_field_is_active, xios_context
    140     USE xios, ONLY: xios_set_current_context
    141     USE wxios, ONLY: missing_val, missing_val_omp
    142 #endif
     134    USE lmdz_xios, ONLY: xios_update_calendar, xios_context_finalize
     135    USE lmdz_xios, ONLY: xios_get_field_attr, xios_field_is_active, xios_context
     136    USE lmdz_xios, ONLY: xios_set_current_context
     137    USE wxios, ONLY: missing_val, using_xios
     138
    143139#ifndef CPP_XIOS
    144140    USE paramLMDZ_phy_mod
     
    520516    REAL dtadd(klon,klev)
    521517
    522 #ifndef CPP_XIOS
    523     REAL, SAVE :: missing_val=nf90_fill_real
    524 #endif
    525518!!   Variables moved to phys_local_var_mod
    526519!!    ! Variables pour le transport convectif
     
    12761269    CALL update_time(pdtphys)
    12771270    phys_tstep=NINT(pdtphys)
    1278 #ifdef CPP_XIOS
    1279 ! switch to XIOS LMDZ physics context
    1280     IF (.NOT. debut .AND. is_omp_master) THEN
    1281        CALL wxios_set_context()
    1282        CALL xios_update_calendar(itap+1)
    1283     ENDIF
    1284 #endif
     1271    IF (.NOT. using_xios) missing_val=nf90_fill_real
     1272
     1273    IF (using_xios) THEN
     1274      ! switch to XIOS LMDZ physics context
     1275      IF (.NOT. debut .AND. is_omp_master) THEN
     1276        CALL wxios_set_context()
     1277        CALL xios_update_calendar(itap+1)
     1278      ENDIF
     1279    ENDIF
    12851280
    12861281    !======================================================================
     
    18411836
    18421837
    1843 #ifdef CPP_XIOS
    1844        IF (is_omp_master) CALL xios_update_calendar(1)
    1845 #endif
     1838       IF (using_xios) THEN
     1839         IF (is_omp_master) CALL xios_update_calendar(1)
     1840       ENDIF
     1841       
    18461842       IF(read_climoz>=1 .AND. create_etat0_limit) CALL regr_horiz_time_climoz(read_climoz,ok_daily_climoz)
    18471843       CALL create_etat0_limit_unstruct
     
    20222018       !=============================================================
    20232019
    2024 #ifdef CPP_XIOS
    2025        ! Get "missing_val" value from XML files (from temperature variable)
    2026        !$OMP MASTER
    2027        CALL xios_get_field_attr("temp",default_value=missing_val_omp)
    2028        !$OMP END MASTER
    2029        !$OMP BARRIER
    2030        missing_val=missing_val_omp
    2031 #endif
    2032 
    2033 #ifdef CPP_XIOS
    2034 ! Need to put this initialisation after phyetat0 as in the coupled model the XIOS context is only
    2035 ! initialised at that moment
    2036        ! Get "missing_val" value from XML files (from temperature variable)
    2037        !$OMP MASTER
    2038        CALL xios_get_field_attr("temp",default_value=missing_val_omp)
    2039        !$OMP END MASTER
    2040        !$OMP BARRIER
    2041        missing_val=missing_val_omp
     2020       IF (using_xios) THEN   
     2021         ! Get "missing_val" value from XML files (from temperature variable)
     2022         IF (is_omp_master) CALL xios_get_field_attr("temp",default_value=missing_val)
     2023         CALL bcast_omp(missing_val)
     2024       ENDIF
     2025
     2026       IF (using_xios) THEN   
     2027         ! Need to put this initialisation after phyetat0 as in the coupled model the XIOS context is only
     2028         ! initialised at that moment
     2029         ! Get "missing_val" value from XML files (from temperature variable)
     2030         IF (is_omp_master) CALL xios_get_field_attr("temp",default_value=missing_val)
     2031         CALL bcast_omp(missing_val)
    20422032       !
    20432033       ! Now we activate some double radiation call flags only if some
    20442034       ! diagnostics are requested, otherwise there is no point in doing this
    2045        IF (is_master) THEN
    2046          !--setting up swaero_diag to TRUE in XIOS case
    2047          IF (xios_field_is_active("topswad").OR.xios_field_is_active("topswad0").OR. &
    2048             xios_field_is_active("solswad").OR.xios_field_is_active("solswad0").OR. &
    2049             xios_field_is_active("topswai").OR.xios_field_is_active("solswai").OR.  &
    2050               (iflag_rrtm==1.AND.(xios_field_is_active("toplwad").OR.xios_field_is_active("toplwad0").OR. &
    2051                                   xios_field_is_active("sollwad").OR.xios_field_is_active("sollwad0"))))  &
    2052             !!!--for now these fields are not in the XML files so they are omitted
    2053             !!!  xios_field_is_active("toplwai").OR.xios_field_is_active("sollwai") !))) &
    2054             swaero_diag=.TRUE.
     2035         IF (is_master) THEN
     2036           !--setting up swaero_diag to TRUE in XIOS case
     2037           IF (xios_field_is_active("topswad").OR.xios_field_is_active("topswad0").OR. &
     2038              xios_field_is_active("solswad").OR.xios_field_is_active("solswad0").OR. &
     2039              xios_field_is_active("topswai").OR.xios_field_is_active("solswai").OR.  &
     2040                (iflag_rrtm==1.AND.(xios_field_is_active("toplwad").OR.xios_field_is_active("toplwad0").OR. &
     2041                                    xios_field_is_active("sollwad").OR.xios_field_is_active("sollwad0"))))  &
     2042              !!!--for now these fields are not in the XML files so they are omitted
     2043              !!!  xios_field_is_active("toplwai").OR.xios_field_is_active("sollwai") !))) &
     2044              swaero_diag=.TRUE.
    20552045 
    2056          !--setting up swaerofree_diag to TRUE in XIOS case
    2057          IF (xios_field_is_active("SWdnSFCcleanclr").OR.xios_field_is_active("SWupSFCcleanclr").OR. &
    2058             xios_field_is_active("SWupTOAcleanclr").OR.xios_field_is_active("rsucsaf").OR.   &
    2059             xios_field_is_active("rsdcsaf") .OR. xios_field_is_active("LWdnSFCcleanclr").OR. &
    2060             xios_field_is_active("LWupTOAcleanclr")) &
    2061             swaerofree_diag=.TRUE.
     2046           !--setting up swaerofree_diag to TRUE in XIOS case
     2047           IF (xios_field_is_active("SWdnSFCcleanclr").OR.xios_field_is_active("SWupSFCcleanclr").OR. &
     2048              xios_field_is_active("SWupTOAcleanclr").OR.xios_field_is_active("rsucsaf").OR.   &
     2049              xios_field_is_active("rsdcsaf") .OR. xios_field_is_active("LWdnSFCcleanclr").OR. &
     2050              xios_field_is_active("LWupTOAcleanclr")) &
     2051              swaerofree_diag=.TRUE.
    20622052 
    2063          !--setting up dryaod_diag to TRUE in XIOS case
    2064          DO naero = 1, naero_tot-1
    2065           IF (xios_field_is_active("dryod550_"//name_aero_tau(naero))) dryaod_diag=.TRUE.
    2066          ENDDO
    2067          !
    2068          !--setting up ok_4xCO2atm to TRUE in XIOS case
    2069          IF (xios_field_is_active("rsut4co2").OR.xios_field_is_active("rlut4co2").OR. &
    2070             xios_field_is_active("rsutcs4co2").OR.xios_field_is_active("rlutcs4co2").OR. &
    2071             xios_field_is_active("rsu4co2").OR.xios_field_is_active("rsucs4co2").OR. &
    2072             xios_field_is_active("rsd4co2").OR.xios_field_is_active("rsdcs4co2").OR. &
    2073             xios_field_is_active("rlu4co2").OR.xios_field_is_active("rlucs4co2").OR. &
    2074             xios_field_is_active("rld4co2").OR.xios_field_is_active("rldcs4co2")) &
    2075             ok_4xCO2atm=.TRUE.
    2076        ENDIF
    2077        !$OMP BARRIER
    2078        CALL bcast(swaero_diag)
    2079        CALL bcast(swaerofree_diag)
    2080        CALL bcast(dryaod_diag)
    2081        CALL bcast(ok_4xCO2atm)
    2082 #endif
     2053           !--setting up dryaod_diag to TRUE in XIOS case
     2054           DO naero = 1, naero_tot-1
     2055             IF (xios_field_is_active("dryod550_"//name_aero_tau(naero))) dryaod_diag=.TRUE.
     2056           ENDDO
     2057           !
     2058          !--setting up ok_4xCO2atm to TRUE in XIOS case
     2059           IF (xios_field_is_active("rsut4co2").OR.xios_field_is_active("rlut4co2").OR. &
     2060              xios_field_is_active("rsutcs4co2").OR.xios_field_is_active("rlutcs4co2").OR. &
     2061              xios_field_is_active("rsu4co2").OR.xios_field_is_active("rsucs4co2").OR. &
     2062              xios_field_is_active("rsd4co2").OR.xios_field_is_active("rsdcs4co2").OR. &
     2063              xios_field_is_active("rlu4co2").OR.xios_field_is_active("rlucs4co2").OR. &
     2064              xios_field_is_active("rld4co2").OR.xios_field_is_active("rldcs4co2")) &
     2065              ok_4xCO2atm=.TRUE.
     2066           ENDIF
     2067           !$OMP BARRIER
     2068           CALL bcast(swaero_diag)
     2069           CALL bcast(swaerofree_diag)
     2070           CALL bcast(dryaod_diag)
     2071           CALL bcast(ok_4xCO2atm)
     2072         ENDIF !using_xios
    20832073       !
    20842074       CALL printflag( tabcntr0,radpas,ok_journe, &
     
    45094499          cool = cool + betalwoff * (cool0 - cool)
    45104500 
    4511 #ifndef CPP_XIOS
    4512           !
    4513           !IM 2eme calcul radiatif pour le cas perturbe ou au moins un
    4514           !IM des taux doit etre different du taux actuel
    4515           !IM Par defaut on a les taux perturbes egaux aux taux actuels
    4516           !
    4517           IF (RCO2_per.NE.RCO2_act.OR. &
    4518               RCH4_per.NE.RCH4_act.OR. &
    4519               RN2O_per.NE.RN2O_act.OR. &
    4520               RCFC11_per.NE.RCFC11_act.OR. &
    4521               RCFC12_per.NE.RCFC12_act) ok_4xCO2atm =.TRUE.
    4522 #endif
     4501          IF (.NOT. using_xios) THEN
     4502            !
     4503            !IM 2eme calcul radiatif pour le cas perturbe ou au moins un
     4504            !IM des taux doit etre different du taux actuel
     4505            !IM Par defaut on a les taux perturbes egaux aux taux actuels
     4506            !
     4507            IF (RCO2_per.NE.RCO2_act.OR. &
     4508                RCH4_per.NE.RCH4_act.OR. &
     4509                RN2O_per.NE.RN2O_act.OR. &
     4510                RCFC11_per.NE.RCFC11_act.OR. &
     4511                RCFC12_per.NE.RCFC12_act) ok_4xCO2atm =.TRUE.
     4512          ENDIF
    45234513   !
    45244514          IF (ok_4xCO2atm) THEN
     
    55585548
    55595549#ifndef CPP_XIOS
    5560     CALL write_paramLMDZ_phy(itap,nid_ctesGCM,ok_sync)
     5550      CALL write_paramLMDZ_phy(itap,nid_ctesGCM,ok_sync)
    55615551#endif
    55625552
     
    56045594       
    56055595       ENDIF
    5606 #ifdef CPP_XIOS
    5607        IF (is_omp_master) CALL xios_context_finalize
     5596
     5597       IF (using_xios) THEN
     5598         IF (is_omp_master) CALL xios_context_finalize
    56085599
    56095600#ifdef INCA
    5610        if (type_trac == 'inca') then
    5611           IF (is_omp_master .and. grid_type==unstructured) THEN
    5612              CALL finalize_inca
    5613           ENDIF
    5614        endif
     5601         if (type_trac == 'inca') then
     5602            IF (is_omp_master .and. grid_type==unstructured) THEN
     5603               CALL finalize_inca
     5604            ENDIF
     5605         endif
    56155606#endif
    5616 
    5617 #endif
     5607       ENDIF
    56185608       WRITE(lunout,*) ' physiq fin, nombre de steps ou cvpas = 1 : ', Ncvpaseq1
    56195609    ENDIF
  • LMDZ6/trunk/libf/phylmd/plevel.F90

    r2346 r4619  
    1212  USE phys_state_var_mod, ONLY: missing_val_nf90
    1313#endif
    14 #ifdef CPP_XIOS
    15   USE wxios, ONLY: missing_val
    16 #endif
     14  USE wxios, ONLY: missing_val_xios => missing_val, using_xios
    1715  IMPLICIT NONE
    1816
     
    6058
    6159! REAL missing_val
    62 #ifndef CPP_XIOS
    6360  REAL :: missing_val
    64 #endif
    6561
    6662! missing_val = nf90_fill_real
    67 
    68 #ifndef CPP_XIOS
    69       missing_val=missing_val_nf90
    70 #endif
     63  IF (using_xios) THEN
     64    missing_val = missing_val_xios
     65  ELSE
     66    missing_val=missing_val_nf90
     67  ENDIF
    7168
    7269  IF (first) THEN
  • LMDZ6/trunk/libf/phylmd/plevel_new.F90

    r2346 r4619  
    1313  USE phys_state_var_mod, ONLY: missing_val_nf90
    1414#endif
    15 #ifdef CPP_XIOS
    16   USE wxios, ONLY: missing_val
    17 #endif
     15  USE wxios, ONLY: missing_val_xios=>missing_val, using_xios
    1816
    1917  IMPLICIT NONE
     
    6260  INTEGER i, k
    6361
    64 ! REAL missing_val
    65 #ifndef CPP_XIOS
    6662  REAL :: missing_val
    67 #endif
    6863
    69 ! missing_val = nf90_fill_real
    70 
    71 #ifndef CPP_XIOS
    72       missing_val=missing_val_nf90
    73 #endif
     64  IF (using_xios) THEN
     65    missing_val=missing_val_xios
     66  ELSE
     67    missing_val=missing_val_nf90
     68  ENDIF
    7469
    7570  IF (first) THEN
  • LMDZ6/trunk/libf/phylmd/readaerosol_mod.F90

    r4103 r4619  
    173173
    174174
    175   SUBROUTINE init_aero_fromfile(flag_aerosol)
     175SUBROUTINE init_aero_fromfile(flag_aerosol)
    176176  USE netcdf
    177177  USE mod_phys_lmdz_para
    178178  USE mod_grid_phy_lmdz, ONLY: grid_type, unstructured
    179 #ifdef CPP_XIOS
    180   USE xios
    181 #endif
     179  USE lmdz_xios
    182180  IMPLICIT NONE
    183181  INTEGER, INTENT(IN) :: flag_aerosol
    184 #ifdef CPP_XIOS
    185182  REAL,ALLOCATABLE :: lat_src(:)
    186183  REAL,ALLOCATABLE :: lon_src(:)
     
    191188  REAL :: null_array(0)
    192189
    193   IF (flag_aerosol>0 .AND. grid_type==unstructured) THEN
     190  IF (using_xios) THEN
     191    IF (flag_aerosol>0 .AND. grid_type==unstructured) THEN
    194192 
    195     IF (is_omp_root) THEN
     193      IF (is_omp_root) THEN
    196194 
    197       IF (is_mpi_root) THEN
     195        IF (is_mpi_root) THEN
    198196   
    199         IF (nf90_open(TRIM(file_aerosol), NF90_NOWRITE, ncid) /= NF90_NOERR) THEN
    200           CALL check_err( nf90_open(TRIM(file_so4), NF90_NOWRITE, ncid), "pb open "//trim(file_so4) )
     197          IF (nf90_open(TRIM(file_aerosol), NF90_NOWRITE, ncid) /= NF90_NOERR) THEN
     198            CALL check_err( nf90_open(TRIM(file_so4), NF90_NOWRITE, ncid), "pb open "//trim(file_so4) )
     199          ENDIF
     200
     201          ! Read and test longitudes
     202          CALL check_err( nf90_inq_dimid(ncid, "lon", dimID),"pb inq dim lon")
     203          CALL check_err( nf90_inquire_dimension(ncid, dimID, len = nbp_lon_src),"pb inq dim lon")
     204          CALL check_err( nf90_inq_varid(ncid, 'lon', varid),"pb inq lon" )
     205          ALLOCATE(lon_src(nbp_lon_src))
     206          CALL check_err( nf90_get_var(ncid, varid, lon_src(:)),"pb get lon" )
     207
     208          ! Read and test latitudes
     209          CALL check_err( nf90_inq_dimid(ncid, "lat", dimID),"pb inq dim lat")
     210          CALL check_err( nf90_inquire_dimension(ncid, dimID, len = nbp_lat_src),"pb inq dim lat")
     211          CALL check_err( nf90_inq_varid(ncid, 'lat', varid),"pb inq lat" )
     212          ALLOCATE(lat_src(nbp_lat_src))
     213          CALL check_err( nf90_get_var(ncid, varid, lat_src(:)),"pb get lat" )
     214          IF (nf90_inq_dimid(ncid, 'lev', dimid) /= NF90_NOERR) THEN
     215            IF (nf90_inq_dimid(ncid, 'presnivs', dimid)/= NF90_NOERR) THEN
     216               CALL check_err(nf90_inq_dimid(ncid, 'PRESNIVS', dimid),'dimension lev,PRESNIVS or presnivs not in file')
     217            ENDIF
     218          ENDIF
     219          CALL check_err( nf90_inquire_dimension(ncid, dimid, len = klev_src),"pb inq dim for PRESNIVS or lev" )
     220          CALL check_err( nf90_close(ncid),"pb in close" )   
    201221        ENDIF
    202222
    203         ! Read and test longitudes
    204         CALL check_err( nf90_inq_dimid(ncid, "lon", dimID),"pb inq dim lon")
    205         CALL check_err( nf90_inquire_dimension(ncid, dimID, len = nbp_lon_src),"pb inq dim lon")
    206         CALL check_err( nf90_inq_varid(ncid, 'lon', varid),"pb inq lon" )
    207         ALLOCATE(lon_src(nbp_lon_src))
    208         CALL check_err( nf90_get_var(ncid, varid, lon_src(:)),"pb get lon" )
    209 
    210         ! Read and test latitudes
    211         CALL check_err( nf90_inq_dimid(ncid, "lat", dimID),"pb inq dim lat")
    212         CALL check_err( nf90_inquire_dimension(ncid, dimID, len = nbp_lat_src),"pb inq dim lat")
    213         CALL check_err( nf90_inq_varid(ncid, 'lat', varid),"pb inq lat" )
    214         ALLOCATE(lat_src(nbp_lat_src))
    215         CALL check_err( nf90_get_var(ncid, varid, lat_src(:)),"pb get lat" )
    216         IF (nf90_inq_dimid(ncid, 'lev', dimid) /= NF90_NOERR) THEN
    217           IF (nf90_inq_dimid(ncid, 'presnivs', dimid)/= NF90_NOERR) THEN
    218              CALL check_err(nf90_inq_dimid(ncid, 'PRESNIVS', dimid),'dimension lev,PRESNIVS or presnivs not in file')
    219           ENDIF
     223        CALL bcast_mpi(nbp_lat_src)
     224        CALL bcast_mpi(nbp_lon_src)
     225        CALL bcast_mpi(klev_src)
     226
     227        IF (is_mpi_root ) THEN
     228          CALL xios_set_domain_attr("domain_aerosol",nj_glo=nbp_lat_src, nj=nbp_lat_src, jbegin=0, latvalue_1d=lat_src)
     229          CALL xios_set_domain_attr("domain_aerosol",ni_glo=nbp_lon_src, ni=nbp_lon_src, ibegin=0, lonvalue_1d=lon_src)
     230        ELSE
     231          CALL xios_set_domain_attr("domain_aerosol",nj_glo=nbp_lat_src, nj=0, jbegin=0, latvalue_1d=null_array )
     232          CALL xios_set_domain_attr("domain_aerosol",ni_glo=nbp_lon_src, ni=0, ibegin=0, lonvalue_1d=null_array)
    220233        ENDIF
    221         CALL check_err( nf90_inquire_dimension(ncid, dimid, len = klev_src),"pb inq dim for PRESNIVS or lev" )
    222         CALL check_err( nf90_close(ncid),"pb in close" )   
     234        CALL xios_set_axis_attr("axis_aerosol",n_glo=klev_src)
     235        CALL xios_set_fieldgroup_attr("aerosols", enabled=.TRUE.)
     236 
    223237      ENDIF
    224 
    225       CALL bcast_mpi(nbp_lat_src)
    226       CALL bcast_mpi(nbp_lon_src)
    227       CALL bcast_mpi(klev_src)
    228 
    229       IF (is_mpi_root ) THEN
    230         CALL xios_set_domain_attr("domain_aerosol",nj_glo=nbp_lat_src, nj=nbp_lat_src, jbegin=0, latvalue_1d=lat_src)
    231         CALL xios_set_domain_attr("domain_aerosol",ni_glo=nbp_lon_src, ni=nbp_lon_src, ibegin=0, lonvalue_1d=lon_src)
    232       ELSE
    233         CALL xios_set_domain_attr("domain_aerosol",nj_glo=nbp_lat_src, nj=0, jbegin=0, latvalue_1d=null_array )
    234         CALL xios_set_domain_attr("domain_aerosol",ni_glo=nbp_lon_src, ni=0, ibegin=0, lonvalue_1d=null_array)
    235       ENDIF
    236       CALL xios_set_axis_attr("axis_aerosol",n_glo=klev_src)
    237       CALL xios_set_fieldgroup_attr("aerosols", enabled=.TRUE.)
    238  
    239     ENDIF
    240238   
    241   ENDIF   
    242 #endif
    243   END SUBROUTINE init_aero_fromfile
     239    ENDIF   
     240  ENDIF !using_xios
     241END SUBROUTINE init_aero_fromfile
    244242
    245243
     
    271269    USE iophy, ONLY : io_lon, io_lat
    272270    USE print_control_mod, ONLY: lunout
    273 #ifdef CPP_XIOS
    274     USE xios
    275 #endif
     271    USE lmdz_xios
    276272    IMPLICIT NONE
    277273     
     
    685681
    686682    IF (grid_type==unstructured) THEN
    687 #ifdef CPP_XIOS
    688683      IF (is_omp_master) THEN
    689684        CALL xios_send_field(TRIM(varname)//"_in",varyear)
     
    702697      CALL scatter_omp(psurf_interp,psurf_out)
    703698      first=.FALSE.
    704 #endif
    705699    ELSE
    706700      ! Scatter global field to local domain at local process
  • LMDZ6/trunk/libf/phylmd/readaerosolstrato.F90

    r4489 r4619  
    1616    USE dimphy
    1717    USE print_control_mod, ONLY: prt_level,lunout
    18 #ifdef CPP_XIOS
    19     USE xios
    20 #endif
     18    USE lmdz_xios
    2119    implicit none
    2220
     
    148146
    149147    IF (grid_type==unstructured) THEN
    150 #ifdef CPP_XIOS
    151148      IF (is_omp_master) THEN
    152149        CALL xios_send_field("taustrat_in",tauaerstrat_mois)
     
    157154      ENDIF
    158155      CALL scatter_omp(tau_aer_strat_mpi,tau_aer_strat)
    159 #endif
    160156    ELSE 
    161157!--scatter on all proc
  • LMDZ6/trunk/libf/phylmd/readaerosolstrato_m.F90

    r4489 r4619  
    2323
    2424
    25   SUBROUTINE init_readaerosolstrato1
    26 #ifdef CPP_XIOS
     25SUBROUTINE init_readaerosolstrato1
    2726  USE netcdf
    2827  USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, &
    2928                      nf95_inq_varid, nf95_open
    3029  USE mod_phys_lmdz_para
    31   USE xios
     30  USE lmdz_xios
    3231!  USE YOERAD, ONLY : NLW
    3332  IMPLICIT NONE
     
    3837  INTEGER :: ncid_in, varid
    3938 
     39  IF (using_xios) THEN
    4040    IF (is_omp_master) THEN 
    4141      IF (is_mpi_root) THEN
     
    6363    ENDIF
    6464   
    65 #endif
    66   END SUBROUTINE init_readaerosolstrato1
     65  ENDIF
     66END SUBROUTINE init_readaerosolstrato1
    6767 
    68   SUBROUTINE init_readaerosolstrato2
    69 #ifdef CPP_XIOS
     68SUBROUTINE init_readaerosolstrato2
    7069  USE netcdf
    7170  USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, &
    7271                      nf95_inq_varid, nf95_open
    7372  USE mod_phys_lmdz_para
    74   USE xios
     73  USE lmdz_xios
    7574!  USE YOERAD, ONLY : NLW
    7675  IMPLICIT NONE
     
    8079  REAL    :: null_array(0)
    8180  INTEGER :: ncid_in, varid
    82 
     81 
     82  IF (using_xios) THEN
    8383    IF (is_omp_master) THEN   
    8484      IF (is_mpi_root) THEN
     
    131131
    132132    ENDIF
    133 #endif   
    134   END SUBROUTINE init_readaerosolstrato2
     133  ENDIF   
     134END SUBROUTINE init_readaerosolstrato2
    135135 
    136136
  • LMDZ6/trunk/libf/phylmd/regr_horiz_time_climoz_m.F90

    r4489 r4619  
    6666  USE regular_lonlat_mod, ONLY: boundslon_reg, boundslat_reg, south, west, east
    6767  USE slopes_m,           ONLY: slopes
    68 #ifdef CPP_XIOS
    69   USE xios
    70 #endif
     68  USE lmdz_xios
    7169  USE mod_phys_lmdz_para, ONLY: is_mpi_root, is_master, is_omp_master, gather, gather_mpi, bcast_mpi, klon_mpi
    7270  USE geometry_mod, ONLY : latitude_deg, ind_cell_glo
     
    240238      CALL bcast_mpi(ntim_ou)
    241239
    242 #ifdef CPP_XIOS   
    243240      IF (is_mpi_root) THEN
    244241        CALL xios_set_domain_attr("domain_climoz",nj_glo=nlat_in, nj=nlat_in, jbegin=0, latvalue_1d=lat_in/deg2rad)
     
    262259      CALL  xios_set_field_attr("tro3_out", enabled=.TRUE.)
    263260      CALL  xios_set_field_attr("tro3_out", enabled=.TRUE.)
    264 #endif
    265261     
    266262      IF (first) THEN
     
    415411    !=============================================================================
    416412     IF (grid_type==unstructured) THEN
    417 #ifdef CPP_XIOS
    418413       nlat_ou=klon_mpi
    419414       
     
    428423       CALL xios_send_field("tro3_in",o3_in3bis(:,:,:,:,:))
    429424       CALL xios_recv_field("tro3_out",o3_regr_lonlat(1,:,:,:,:))
    430 #endif
    431425     ELSE
    432426         
     
    462456     nlat_ou=nbp_lat
    463457     IF (grid_type==unstructured) THEN
    464 #ifdef CPP_XIOS
    465458       CALL xios_send_field('o3_out',o3_out3)
    466459       ndims=3
    467460       ALLOCATE(o3_out3_glo(nlat_ou, nlev_in, ntim_ou, read_climoz))
    468461       CALL gather_mpi(o3_out3(1,:,:,:,:), o3_out3_glo)
    469 #endif
    470462     ENDIF
    471463
     
    508500   
    509501     IF (grid_type==unstructured) THEN
    510 #ifdef CPP_XIOS
    511502       nlat_ou=klon_mpi
    512503
     
    522513       IF(.NOT.lprev) o3_regr_lat(:,:, 0, :) = o3_regr_lat(:,:,12,:)
    523514       IF(.NOT.lnext) o3_regr_lat(:,:,13, :) = o3_regr_lat(:,:, 1,:)
    524 #endif       
    525515     
    526516     ELSE
  • LMDZ6/trunk/libf/phylmd/rrtm/readaerosolstrato1_rrtm.F90

    r4489 r4619  
    1818    USE YOERAD, ONLY : NLW
    1919    USE YOMCST
    20 #ifdef CPP_XIOS
    21     USE xios
    22 #endif
     20    USE lmdz_xios
    2321
    2422    IMPLICIT NONE
     
    167165   
    168166    IF (grid_type==unstructured) THEN
    169 #ifdef CPP_XIOS
    170167      IF (is_omp_master) THEN
    171168        ALLOCATE(tauaerstrat_mpi(klon_mpi,klev))
     
    176173      ENDIF
    177174      CALL scatter_omp(tauaerstrat_mpi,tau_aer_strat)
    178 #endif
    179175    ELSE 
    180176      CALL scatter(tauaerstrat_mois_glo,tau_aer_strat)
  • LMDZ6/trunk/libf/phylmd/rrtm/readaerosolstrato2_rrtm.F90

    r4489 r4619  
    1919    USE YOERAD, ONLY : NLW
    2020    USE YOMCST
    21 #ifdef CPP_XIOS
    22     USE xios
    23 #endif
     21    USE lmdz_xios
    2422
    2523    IMPLICIT NONE
     
    282280
    283281      IF (grid_type==unstructured) THEN
    284 
    285 #ifdef CPP_XIOS
    286282
    287283        IF (is_omp_master) THEN
     
    310306        CALL scatter_omp(cgaerstrat_mpi,cg_aer_strat)
    311307        CALL scatter_omp(taulwaerstrat_mpi,taulw_aer_strat)
    312 #endif
    313308      ELSE 
    314309       
  • LMDZ6/trunk/libf/phylmd/undefSTD.F90

    r4593 r4619  
    88  USE phys_state_var_mod
    99#endif
    10 #ifdef CPP_XIOS
    11   USE wxios, ONLY: missing_val
    12 #endif
     10  USE wxios, ONLY: missing_val_xios => missing_val, using_xios
    1311
    1412  IMPLICIT NONE
    1513  include "clesphys.h"
    16 #ifndef CPP_XIOS
    1714  REAL :: missing_val
    18 #endif
    1915
    2016  ! ====================================================================
     
    5955
    6056! missing_val = nf90_fill_real
    61 #ifndef CPP_XIOS
     57  IF (using_xios) THEN
     58    missing_val=missing_val_xios
     59  ELSE
    6260      missing_val=missing_val_nf90
    63 #endif
     61  ENDIF
    6462
    6563  DO n = 1, nout
  • LMDZ6/trunk/libf/phylmdiso/limit_read_mod.F90

    r4143 r4619  
    4040  USE surface_data
    4141  USE mod_phys_lmdz_para
    42 #ifdef CPP_XIOS
    43   USE XIOS
    44 #endif
     42  USE lmdz_xios
    4543  IMPLICIT NONE
    4644    INTEGER, INTENT(IN) :: first_day
     
    4947    IF ( type_ocean /= 'couple') THEN
    5048      IF (grid_type==unstructured) THEN
    51 #ifdef CPP_XIOS
    52         IF (is_omp_master) CALL xios_set_file_attr("limit_read",enabled=.TRUE.,record_offset=first_day)
    53 #endif
     49          IF (is_omp_master) CALL xios_set_file_attr("limit_read",enabled=.TRUE.,record_offset=first_day)
    5450      ENDIF 
    5551    ENDIF
     
    288284    USE phys_cal_mod, ONLY : calend, year_len
    289285    USE print_control_mod, ONLY: lunout, prt_level
    290 #ifdef CPP_XIOS
    291     USE XIOS, ONLY: xios_recv_field
    292 #endif
     286    USE lmdz_XIOS, ONLY: xios_recv_field
    293287   
    294288    IMPLICIT NONE
     
    416410      IF (grid_type==unstructured) THEN
    417411
    418 #ifdef CPP_XIOS
    419412        IF ( type_ocean /= 'couple') THEN
    420413
     
    450443          CALL Scatter_omp(rug_mpi, rugos)
    451444       END IF
    452 #endif
    453 
    454  
     445
    455446     ELSE      ! grid_type==regular
    456447
  • LMDZ6/trunk/libf/phylmdiso/pbl_surface_mod.F90

    r4531 r4619  
    412412    use phys_output_var_mod, only: tkt, tks, taur, sss
    413413    use blowing_snow_ini_mod, only : zeta_bs
    414 #ifdef CPP_XIOS
    415     USE wxios, ONLY: missing_val
    416 #else
    417     use netcdf, only: missing_val => nf90_fill_real
    418 #endif
    419 
    420      
    421 
     414    USE wxios, ONLY: missing_val_xios => missing_val, using_xios
     415    use netcdf, only: nf90_fill_real
    422416
    423417    IMPLICIT NONE
     
    944938    REAL, DIMENSION(klon)       :: uzon_w, vmer_w, speed_w, zri1_w, pref_w !speed_w, zri1_w, pref_w, added by Fuxing WANG, 04/03/2015
    945939    REAL, DIMENSION(klon)       :: zgeo1_w, tair1_w, qair1_w, tairsol_w
    946 
     940   
    947941!!! jyg le 25/03/2013
    948942!!    Variables intermediaires pour le raccord des deux colonnes \`a la surface
     
    10511045    ! compression of delta_sst, delta_sal, ds_ns, dt_ns, dter, dser,
    10521046    ! dt_ds, tkt, tks, taur, sss on ocean points
    1053 
     1047    REAL :: missing_val
    10541048#ifdef ISO
    10551049    REAL, DIMENSION(klon)       :: h1
     
    10631057! End of declarations
    10641058!****************************************************************************************
    1065 
     1059   
    10661060      IF (prt_level >=10) print *,' -> pbl_surface, itap ',itap
     1061     
     1062      IF (using_xios) THEN
     1063        missing_val = missing_val_xios
     1064      ELSE
     1065        missing_val = nf90_fill_real
     1066      ENDIF
    10671067!
    10681068!!jyg      iflag_split = mod(iflag_pbl_split,2)
  • LMDZ6/trunk/libf/phylmdiso/phyaqua_mod.F90

    r3927 r4619  
    536536    USE mod_phys_lmdz_para, ONLY: is_omp_master, klon_mpi
    537537    USE mod_phys_lmdz_transfert_para, ONLY: gather_omp
    538 #ifdef CPP_XIOS
    539     USE xios
    540 #endif
     538    USE lmdz_xios
    541539    IMPLICIT NONE
    542540
     
    558556      ! on the whole physics grid
    559557 
    560 #ifdef CPP_XIOS
    561558    PRINT *, 'writelim: Ecriture du fichier limit'
    562559
     
    584581    CALL gather_omp(phy_rug, phy_mpi)
    585582    IF (is_omp_master) CALL xios_send_field('rug_limout',phy_mpi)
    586 #endif
     583
    587584  END SUBROUTINE writelim_unstruct
    588585
  • LMDZ6/trunk/libf/phylmdiso/phyetat0_mod.F90

    r4613 r4619  
    4747  USE ocean_slab_mod,   ONLY: nslay, tslab, seaice, tice, ocean_slab_init
    4848  USE time_phylmdz_mod, ONLY: init_iteration, pdtphys, itau_phy
    49 #ifdef CPP_XIOS
    50   USE wxios, ONLY: missing_val
    51 #else
    52   use netcdf, only: missing_val => nf90_fill_real
    53 #endif
     49  USE wxios, ONLY: missing_val_xios => missing_val, using_xios
     50  use netcdf, only:  nf90_fill_real
    5451  use config_ocean_skin_m, only: activate_ocean_skin
    5552#ifdef ISO
     
    108105  REAL :: lon_startphy(klon), lat_startphy(klon)
    109106  CHARACTER(LEN=maxlen) :: tname, t(2)
    110 
     107  REAL :: missing_val
    111108#ifdef ISO
    112109  REAL xtsnow(niso,klon, nbsrf)
     
    119116
    120117  ! Ouvrir le fichier contenant l'etat initial:
     118  IF (using_xios) THEN
     119    missing_val = missing_val_xios
     120  ELSE
     121    missing_val =  nf90_fill_real
     122  ENDIF
    121123
    122124  CALL open_startphy(fichnom)
  • LMDZ6/trunk/libf/phylmdiso/phys_output_mod.F90

    r4524 r4619  
    4747    USE vertical_layers_mod, ONLY: ap,bp,preff,presnivs, aps, bps, pseudoalt
    4848    USE time_phylmdz_mod, ONLY: day_ini, itau_phy, start_time, annee_ref, day_ref
    49 #ifdef CPP_XIOS
    5049    ! ug Pour les sorties XIOS
    5150    USE wxios
    52 #endif
    5351#ifdef ISO
    5452    USE isotopes_mod, ONLY: isoName,iso_HTO
     
    140138    REAL, DIMENSION(klev+1)   :: lev_index
    141139               
    142 #ifdef CPP_XIOS
    143140    ! ug Variables utilis\'ees pour r\'ecup\'erer le calendrier pour xios
    144141    INTEGER :: x_an, x_mois, x_jour
     
    146143    INTEGER :: ini_an, ini_mois, ini_jour
    147144    REAL :: ini_heure
    148 #endif
    149145    INTEGER                         :: ISW
    150146    REAL, DIMENSION(NSW)            :: wl1_sun, wl2_sun !wavelength bounds (in um) for SW
     
    326322     ENDIF
    327323
    328 #ifdef CPP_XIOS
    329     ! ug R\'eglage du calendrier xios
    330     !Temps julian => an, mois, jour, heure
    331     CALL ju2ymds(zjulian, x_an, x_mois, x_jour, x_heure)
    332     CALL ju2ymds(zjulian_start, ini_an, ini_mois, ini_jour, ini_heure)
    333     CALL wxios_set_cal(dtime, calend, x_an, x_mois, x_jour, x_heure, ini_an, &
    334                        ini_mois, ini_jour, ini_heure )
    335 #endif
     324    IF (using_xios) THEN
     325      ! ug R\'eglage du calendrier xios
     326      !Temps julian => an, mois, jour, heure
     327      CALL ju2ymds(zjulian, x_an, x_mois, x_jour, x_heure)
     328      CALL ju2ymds(zjulian_start, ini_an, ini_mois, ini_jour, ini_heure)
     329      CALL wxios_set_cal(dtime, calend, x_an, x_mois, x_jour, x_heure, ini_an, &
     330                         ini_mois, ini_jour, ini_heure )
     331    ENDIF
    336332
    337333!!!!!!!!!!!!!!!!!!!!!!! Boucle sur les fichiers !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    366362
    367363
    368 #ifdef CPP_XIOS
     364    IF (using_xios) THEN
    369365!!! Ouverture de chaque fichier XIOS !!!!!!!!!!!
    370     IF (.not. ok_all_xml) THEN
     366      IF (.not. ok_all_xml) THEN
     367        IF (prt_level >= 10) THEN
     368         print*,'phys_output_open: call wxios_add_file with phys_out_filenames(iff)=',trim(phys_out_filenames(iff))   
     369        ENDIF
     370        CALL wxios_add_file(phys_out_filenames(iff),chtimestep(iff),lev_files(iff)) 
     371      ENDIF
     372
     373!!! Declaration des axes verticaux de chaque fichier:
    371374      IF (prt_level >= 10) THEN
    372         print*,'phys_output_open: call wxios_add_file with phys_out_filenames(iff)=',trim(phys_out_filenames(iff))   
     375        print*,'phys_output_open: Declare vertical axes for each file'
    373376      ENDIF
    374       CALL wxios_add_file(phys_out_filenames(iff),chtimestep(iff),lev_files(iff)) 
    375     ENDIF
    376 
    377 !!! Declaration des axes verticaux de chaque fichier:
    378     IF (prt_level >= 10) THEN
    379       print*,'phys_output_open: Declare vertical axes for each file'
    380     ENDIF
    381 
    382    IF (iff.LE.6.OR.iff.EQ.10) THEN
    383     CALL wxios_add_vaxis("presnivs", &
    384             levmax(iff) - levmin(iff) + 1, presnivs(levmin(iff):levmax(iff)))
    385     CALL wxios_add_vaxis("Ahyb", &
     377
     378      IF (iff.LE.6.OR.iff.EQ.10) THEN
     379        CALL wxios_add_vaxis("presnivs", &
     380             levmax(iff) - levmin(iff) + 1, presnivs(levmin(iff):levmax(iff)))
     381        CALL wxios_add_vaxis("Ahyb", &
    386382            levmax(iff) - levmin(iff) + 1, aps(levmin(iff):levmax(iff)), positif='down', &
    387383            bnds=Ahyb_bounds(levmin(iff):levmax(iff),:))
    388     CALL wxios_add_vaxis("Bhyb", &
     384        CALL wxios_add_vaxis("Bhyb", &
    389385            levmax(iff) - levmin(iff) + 1, bps(levmin(iff):levmax(iff)), positif='down', &
    390386            bnds=Bhyb_bounds(levmin(iff):levmax(iff),:))
    391     CALL wxios_add_vaxis("klev", levmax(iff) - levmin(iff) + 1, &
     387        CALL wxios_add_vaxis("klev", levmax(iff) - levmin(iff) + 1, &
    392388                          lev_index(levmin(iff):levmax(iff)))
    393     CALL wxios_add_vaxis("klevp1", klev+1, &
     389        CALL wxios_add_vaxis("klevp1", klev+1, &
    394390                          lev_index(1:klev+1))
    395     CALL wxios_add_vaxis("bnds", 2, (/1.,2./))
    396 
    397     CALL wxios_add_vaxis("Alt", &
     391        CALL wxios_add_vaxis("bnds", 2, (/1.,2./))
     392
     393        CALL wxios_add_vaxis("Alt", &
    398394            levmax(iff) - levmin(iff) + 1, pseudoalt)
    399 
    400     ! wl1_sun/wl2_sun: minimum/maximum bound of wavelength (in um)
    401     SELECT CASE(NSW)
    402       CASE(6)
    403         wl1_sun(1:6) = [0.180, 0.250, 0.440, 0.690, 1.190, 2.380]
    404         wl2_sun(1:6) = [0.250, 0.440, 0.690, 1.190, 2.380, 4.000]
    405       CASE(2)
    406         wl1_sun(1:2) = [0.250, 0.690]
    407         wl2_sun(1:2) = [0.690, 4.000]
    408     END SELECT
    409 
    410     DO ISW=1, NSW
    411      wn1_sun(ISW)=1.e+6/wl1_sun(ISW)
    412      wn2_sun(ISW)=1.e+6/wl2_sun(ISW)
    413      spbnds_sun(ISW,1)=wn2_sun(ISW)
    414      spbnds_sun(ISW,2)=wn1_sun(ISW)
    415      spectband(ISW)=(wn1_sun(ISW)+wn2_sun(ISW))/2
    416     ENDDO
     395 
     396        ! wl1_sun/wl2_sun: minimum/maximum bound of wavelength (in um)
     397        SELECT CASE(NSW)
     398          CASE(6)
     399          wl1_sun(1:6) = [0.180, 0.250, 0.440, 0.690, 1.190, 2.380]
     400          wl2_sun(1:6) = [0.250, 0.440, 0.690, 1.190, 2.380, 4.000]
     401        CASE(2)
     402          wl1_sun(1:2) = [0.250, 0.690]
     403          wl2_sun(1:2) = [0.690, 4.000]
     404        END SELECT
     405
     406        DO ISW=1, NSW
     407          wn1_sun(ISW)=1.e+6/wl1_sun(ISW)
     408          wn2_sun(ISW)=1.e+6/wl2_sun(ISW)
     409          spbnds_sun(ISW,1)=wn2_sun(ISW)
     410          spbnds_sun(ISW,2)=wn1_sun(ISW)
     411          spectband(ISW)=(wn1_sun(ISW)+wn2_sun(ISW))/2
     412        ENDDO
    417413!
    418414!!! ajout axe vertical spectband : solar band number
    419     CALL wxios_add_vaxis("spectband", NSW, spectband, positif='down')
    420    ELSE
     415        CALL wxios_add_vaxis("spectband", NSW, spectband, positif='down')
     416      ELSE
    421417    ! NMC files
    422     CALL wxios_add_vaxis("plev", &
     418        CALL wxios_add_vaxis("plev", &
    423419            levmax(iff) - levmin(iff) + 1, rlevSTD(levmin(iff):levmax(iff)))
    424    ENDIF
    425 #endif
     420      ENDIF
     421    ENDIF
    426422
    427423        IF (clef_files(iff)) THEN
  • LMDZ6/trunk/libf/phylmdiso/physiq_mod.F90

    r4613 r4619  
    7676    USE vampir
    7777    USE write_field_phy
    78 #ifdef CPP_XIOS
    79     USE wxios, ONLY: g_ctx, wxios_set_context
    80 #endif
     78    USE wxios, ONLY: g_ctx, wxios_set_context, using_xios
    8179    USE lscp_mod, ONLY : lscp
    8280    USE lmdz_wake_ini, ONLY : wake_ini
     
    134132
    135133
    136 #ifdef CPP_XIOS
    137     USE xios, ONLY: xios_update_calendar, xios_context_finalize
    138     USE xios, ONLY: xios_get_field_attr, xios_field_is_active, xios_context
    139     USE xios, ONLY: xios_set_current_context
    140     USE wxios, ONLY: missing_val, missing_val_omp
    141 #endif
     134    USE lmdz_xios, ONLY: xios_update_calendar, xios_context_finalize
     135    USE lmdz_xios, ONLY: xios_get_field_attr, xios_field_is_active, xios_context
     136    USE lmdz_xios, ONLY: xios_set_current_context
     137    USE wxios, ONLY: missing_val_xios => missing_val
     138
    142139#ifndef CPP_XIOS
    143140    USE paramLMDZ_phy_mod
     
    13261323    real xtql1(ntraciso,klon),xtql2(ntraciso,klon),corrxtql(ntraciso)
    13271324#endif
    1328 
     1325   
    13291326    REAL pi
    13301327
     
    13431340    CALL update_time(pdtphys)
    13441341    phys_tstep=NINT(pdtphys)
     1342    IF (.NOT. using_xios) missing_val=nf90_fill_real
    13451343#ifdef CPP_XIOS
    13461344! switch to XIOS LMDZ physics context
     
    21502148       !=============================================================
    21512149
    2152 #ifdef CPP_XIOS
    2153        ! Get "missing_val" value from XML files (from temperature variable)
    2154        !$OMP MASTER
    2155        CALL xios_get_field_attr("temp",default_value=missing_val_omp)
    2156        !$OMP END MASTER
    2157        !$OMP BARRIER
    2158        missing_val=missing_val_omp
    2159 #endif
    2160 
    2161 #ifdef CPP_XIOS
     2150       IF (using_xios) THEN   
     2151         ! Get "missing_val" value from XML files (from temperature variable)
     2152         IF (is_omp_master) CALL xios_get_field_attr("temp",default_value=missing_val)
     2153         CALL bcast_omp(missing_val)
     2154       ENDIF
     2155
     2156      IF (using_xios) THEN
    21622157! Need to put this initialisation after phyetat0 as in the coupled model the XIOS context is only
    21632158! initialised at that moment
    21642159       ! Get "missing_val" value from XML files (from temperature variable)
    2165        !$OMP MASTER
    2166        CALL xios_get_field_attr("temp",default_value=missing_val_omp)
    2167        !$OMP END MASTER
    2168        !$OMP BARRIER
    2169        missing_val=missing_val_omp
     2160        IF (is_omp_master) CALL xios_get_field_attr("temp",default_value=missing_val)
     2161        CALL bcast_omp(missing_val)
     2162       
    21702163       !
    21712164       ! Now we activate some double radiation call flags only if some
     
    22082201       CALL bcast(dryaod_diag)
    22092202       CALL bcast(ok_4xCO2atm)
    2210 #endif
     2203
     2204     ENDIF !using_xios
     2205
    22112206       !
    22122207       CALL printflag( tabcntr0,radpas,ok_journe, &
     
    57735768          cool = cool + betalwoff * (cool0 - cool)
    57745769 
    5775 #ifndef CPP_XIOS
    5776           !
    5777           !IM 2eme calcul radiatif pour le cas perturbe ou au moins un
    5778           !IM des taux doit etre different du taux actuel
    5779           !IM Par defaut on a les taux perturbes egaux aux taux actuels
    5780           !
    5781           IF (RCO2_per.NE.RCO2_act.OR. &
    5782               RCH4_per.NE.RCH4_act.OR. &
    5783               RN2O_per.NE.RN2O_act.OR. &
    5784               RCFC11_per.NE.RCFC11_act.OR. &
    5785               RCFC12_per.NE.RCFC12_act) ok_4xCO2atm =.TRUE.
    5786 #endif
     5770          IF (.NOT. using_xios) THEN
     5771            !
     5772            !IM 2eme calcul radiatif pour le cas perturbe ou au moins un
     5773            !IM des taux doit etre different du taux actuel
     5774            !IM Par defaut on a les taux perturbes egaux aux taux actuels
     5775            !
     5776            IF (RCO2_per.NE.RCO2_act.OR. &
     5777                RCH4_per.NE.RCH4_act.OR. &
     5778                RN2O_per.NE.RN2O_act.OR. &
     5779                RCFC11_per.NE.RCFC11_act.OR. &
     5780                RCFC12_per.NE.RCFC12_act) ok_4xCO2atm =.TRUE.
     5781          ENDIF
    57875782   !
    57885783          IF (ok_4xCO2atm) THEN
     
    70057000! Pour XIOS : On remet des variables a .false. apres un premier appel
    70067001    IF (debut) THEN
    7007 #ifdef CPP_XIOS
    7008       swaero_diag=.FALSE.
    7009       swaerofree_diag=.FALSE.
    7010       dryaod_diag=.FALSE.
    7011       ok_4xCO2atm= .FALSE.
    7012 !      write (lunout,*)'ok_4xCO2atm= ',swaero_diag, swaerofree_diag, dryaod_diag, ok_4xCO2atm
    7013 
    7014       IF (is_master) THEN
    7015         !--setting up swaero_diag to TRUE in XIOS case
    7016         IF (xios_field_is_active("topswad").OR.xios_field_is_active("topswad0").OR. &
    7017            xios_field_is_active("solswad").OR.xios_field_is_active("solswad0").OR. &
    7018            xios_field_is_active("topswai").OR.xios_field_is_active("solswai").OR.  &
    7019              (iflag_rrtm==1.AND.(xios_field_is_active("toplwad").OR.xios_field_is_active("toplwad0").OR. &
    7020                                  xios_field_is_active("sollwad").OR.xios_field_is_active("sollwad0"))))  &
    7021            !!!--for now these fields are not in the XML files so they are omitted
    7022            !!!  xios_field_is_active("toplwai").OR.xios_field_is_active("sollwai") !))) &
    7023            swaero_diag=.TRUE.
    7024 
    7025         !--setting up swaerofree_diag to TRUE in XIOS case
    7026         IF (xios_field_is_active("SWdnSFCcleanclr").OR.xios_field_is_active("SWupSFCcleanclr").OR. &
    7027            xios_field_is_active("SWupTOAcleanclr").OR.xios_field_is_active("rsucsaf").OR.   &
    7028            xios_field_is_active("rsdcsaf") .OR. xios_field_is_active("LWdnSFCcleanclr").OR. &
    7029            xios_field_is_active("LWupTOAcleanclr")) &
    7030            swaerofree_diag=.TRUE.
    7031 
    7032         !--setting up dryaod_diag to TRUE in XIOS case
    7033         DO naero = 1, naero_tot-1
    7034          IF (xios_field_is_active("dryod550_"//name_aero_tau(naero))) dryaod_diag=.TRUE.
    7035         ENDDO
    7036         !
    7037         !--setting up ok_4xCO2atm to TRUE in XIOS case
    7038         IF (xios_field_is_active("rsut4co2").OR.xios_field_is_active("rlut4co2").OR. &
    7039            xios_field_is_active("rsutcs4co2").OR.xios_field_is_active("rlutcs4co2").OR. &
    7040            xios_field_is_active("rsu4co2").OR.xios_field_is_active("rsucs4co2").OR. &
    7041            xios_field_is_active("rsd4co2").OR.xios_field_is_active("rsdcs4co2").OR. &
    7042            xios_field_is_active("rlu4co2").OR.xios_field_is_active("rlucs4co2").OR. &
    7043            xios_field_is_active("rld4co2").OR.xios_field_is_active("rldcs4co2")) &
    7044            ok_4xCO2atm=.TRUE.
    7045       ENDIF
    7046       !$OMP BARRIER
    7047       CALL bcast(swaero_diag)
    7048       CALL bcast(swaerofree_diag)
    7049       CALL bcast(dryaod_diag)
    7050       CALL bcast(ok_4xCO2atm)
    7051 !      write (lunout,*)'ok_4xCO2atm= ',swaero_diag, swaerofree_diag, dryaod_diag, ok_4xCO2atm
    7052 #endif
     7002
     7003      IF (using_xios) THEN
     7004        swaero_diag=.FALSE.
     7005        swaerofree_diag=.FALSE.
     7006        dryaod_diag=.FALSE.
     7007        ok_4xCO2atm= .FALSE.
     7008!       write (lunout,*)'ok_4xCO2atm= ',swaero_diag, swaerofree_diag, dryaod_diag, ok_4xCO2atm
     7009
     7010        IF (is_master) THEN
     7011          !--setting up swaero_diag to TRUE in XIOS case
     7012          IF (xios_field_is_active("topswad").OR.xios_field_is_active("topswad0").OR. &
     7013             xios_field_is_active("solswad").OR.xios_field_is_active("solswad0").OR. &
     7014             xios_field_is_active("topswai").OR.xios_field_is_active("solswai").OR.  &
     7015               (iflag_rrtm==1.AND.(xios_field_is_active("toplwad").OR.xios_field_is_active("toplwad0").OR. &
     7016                                   xios_field_is_active("sollwad").OR.xios_field_is_active("sollwad0"))))  &
     7017             !!!--for now these fields are not in the XML files so they are omitted
     7018             !!!  xios_field_is_active("toplwai").OR.xios_field_is_active("sollwai") !))) &
     7019             swaero_diag=.TRUE.
     7020
     7021          !--setting up swaerofree_diag to TRUE in XIOS case
     7022          IF (xios_field_is_active("SWdnSFCcleanclr").OR.xios_field_is_active("SWupSFCcleanclr").OR. &
     7023             xios_field_is_active("SWupTOAcleanclr").OR.xios_field_is_active("rsucsaf").OR.   &
     7024             xios_field_is_active("rsdcsaf") .OR. xios_field_is_active("LWdnSFCcleanclr").OR. &
     7025             xios_field_is_active("LWupTOAcleanclr")) &
     7026             swaerofree_diag=.TRUE.
     7027
     7028          !--setting up dryaod_diag to TRUE in XIOS case
     7029          DO naero = 1, naero_tot-1
     7030           IF (xios_field_is_active("dryod550_"//name_aero_tau(naero))) dryaod_diag=.TRUE.
     7031          ENDDO
     7032          !
     7033          !--setting up ok_4xCO2atm to TRUE in XIOS case
     7034          IF (xios_field_is_active("rsut4co2").OR.xios_field_is_active("rlut4co2").OR. &
     7035             xios_field_is_active("rsutcs4co2").OR.xios_field_is_active("rlutcs4co2").OR. &
     7036             xios_field_is_active("rsu4co2").OR.xios_field_is_active("rsucs4co2").OR. &
     7037             xios_field_is_active("rsd4co2").OR.xios_field_is_active("rsdcs4co2").OR. &
     7038             xios_field_is_active("rlu4co2").OR.xios_field_is_active("rlucs4co2").OR. &
     7039             xios_field_is_active("rld4co2").OR.xios_field_is_active("rldcs4co2")) &
     7040             ok_4xCO2atm=.TRUE.
     7041        ENDIF
     7042        !$OMP BARRIER
     7043        CALL bcast(swaero_diag)
     7044        CALL bcast(swaerofree_diag)
     7045        CALL bcast(dryaod_diag)
     7046        CALL bcast(ok_4xCO2atm)
     7047!        write (lunout,*)'ok_4xCO2atm= ',swaero_diag, swaerofree_diag, dryaod_diag, ok_4xCO2atm
     7048      ENDIF !using_xios
    70537049    ENDIF
    70547050
     
    71127108       
    71137109       ENDIF
    7114 #ifdef CPP_XIOS
    7115        IF (is_omp_master) CALL xios_context_finalize
     7110       
     7111       IF (using_xios) THEN
     7112         IF (is_omp_master) CALL xios_context_finalize
    71167113
    71177114#ifdef INCA
    7118        if (type_trac == 'inca') then
    7119           IF (is_omp_master .and. grid_type==unstructured) THEN
    7120              CALL finalize_inca
    7121           ENDIF
    7122        endif
    7123 #endif
    7124 
    7125 #endif
     7115         if (type_trac == 'inca') then
     7116            IF (is_omp_master .and. grid_type==unstructured) THEN
     7117               CALL finalize_inca
     7118            ENDIF
     7119         endif
     7120#endif
     7121       ENDIF !using_xios
    71267122       WRITE(lunout,*) ' physiq fin, nombre de steps ou cvpas = 1 : ', Ncvpaseq1
    71277123    ENDIF
Note: See TracChangeset for help on using the changeset viewer.