Ignore:
Timestamp:
Oct 19, 2023, 4:02:57 PM (11 months ago)
Author:
idelkadi
Message:

Merged trunk changes -r4488:4726 LMDZ_ECRad branch

Location:
LMDZ6/branches/LMDZ_ECRad
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/LMDZ_ECRad

  • LMDZ6/branches/LMDZ_ECRad/libf/phylmd/cosp/cosp_output_write_mod.F90

    r3308 r4727  
    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   
Note: See TracChangeset for help on using the changeset viewer.