Ignore:
Timestamp:
Sep 5, 2014, 5:42:24 PM (10 years ago)
Author:
Laurent Fairhead
Message:

Suite (et fin?) des modifications pour permettre un controle 'tout xml'
des fichiers de sorties XIOS.
Un nouveau paramètre logique est introduit, ok_all_xml, false par défaut, et lu
dans le run.def qui permet de faire du 'tout xml'


Follow-up modifications to ensure total xlm control over the output files
from XIOS.
A new logical parameter, ok_all_wml, is introduced. False by default, it is
read from the run.def file and, if true, will give over control to the
XIOS xml files

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/iophy.F90

    r2097 r2114  
    204204  IMPLICIT NONE
    205205  include 'dimensions.h'
     206  include 'clesphys.h'
    206207   
    207208    character*(*), INTENT(IN) :: name
     
    227228    IF((.NOT. is_using_mpi) .OR. is_mpi_root) THEN
    228229        ! ug Création du fichier
     230      IF (.not. ok_all_xml) THEN
    229231        CALL wxios_add_file(name, ffreq, lev)
     232      ENDIF
    230233    END IF
    231234#endif
     
    603606
    604607#ifdef CPP_XIOS
    605       IF ( var%flag(iff)<=lev_files(iff) ) THEN
    606         CALL wxios_add_field_to_file(var%name, 2, iff, phys_out_filenames(iff), &
    607         var%description, var%unit, var%flag(iff), typeecrit)
    608         IF (prt_level >= 10) THEN
    609           WRITE(lunout,*) 'histdef2d: call wxios_add_field_to_file var%name iff: ', &
    610                           trim(var%name),iff
     608      IF (.not. ok_all_xml) THEN
     609        IF ( var%flag(iff)<=lev_files(iff) ) THEN
     610          CALL wxios_add_field_to_file(var%name, 2, iff, phys_out_filenames(iff), &
     611          var%description, var%unit, var%flag(iff), typeecrit)
     612          IF (prt_level >= 10) THEN
     613            WRITE(lunout,*) 'histdef2d: call wxios_add_field_to_file var%name iff: ', &
     614                            trim(var%name),iff
     615          ENDIF
    611616        ENDIF
    612617      ENDIF
     
    688693
    689694#ifdef CPP_XIOS
    690       IF ( var%flag(iff)<=lev_files(iff) ) THEN
    691         CALL wxios_add_field_to_file(var%name, 3, iff, phys_out_filenames(iff), &
    692         var%description, var%unit, var%flag(iff), typeecrit)
    693         IF (prt_level >= 10) THEN
    694           WRITE(lunout,*) 'histdef3d: call wxios_add_field_to_file var%name iff: ', &
    695                           trim(var%name),iff
    696         ENDIF
    697       ENDIF
     695       IF (.not. ok_all_xml) THEN
     696         IF ( var%flag(iff)<=lev_files(iff) ) THEN
     697         CALL wxios_add_field_to_file(var%name, 3, iff, phys_out_filenames(iff), &
     698         var%description, var%unit, var%flag(iff), typeecrit)
     699           IF (prt_level >= 10) THEN
     700             WRITE(lunout,*) 'histdef3d: call wxios_add_field_to_file var%name iff: ', &
     701                             trim(var%name),iff
     702           ENDIF
     703         ENDIF
     704       ENDIF
    698705#endif
    699706#ifndef CPP_IOIPSL_NO_OUTPUT
     
    890897  INCLUDE 'dimensions.h'
    891898  INCLUDE 'iniprint.h'
     899  include 'clesphys.h'
    892900
    893901    TYPE(ctrl_out), INTENT(IN) :: var
     
    922930!$OMP MASTER
    923931      !Si phase de définition.... on définit
     932      IF (.not. ok_all_xml) THEN
     933      if (prt_level >= 10) then
     934      write(lunout,*)"histwrite2d_phy: .not.vars_defined ; time to define ", &
     935                     trim(var%name)
     936      endif
    924937      DO iff=iff_beg, iff_end
    925938         IF (clef_files(iff)) THEN
     
    927940         ENDIF
    928941      ENDDO
     942      ENDIF
    929943!$OMP END MASTER
    930944  ELSE
     
    944958! La boucle sur les fichiers:
    945959      firstx=.true.
    946       DO iff=iff_beg, iff_end
     960
     961      IF (ok_all_xml) THEN
     962#ifdef CPP_XIOS
     963          if (prt_level >= 10) then
     964             write(lunout,*)'Dans iophy histwrite2D,var%name ',&
     965                             trim(var%name)                       
     966          endif
     967          CALL xios_send_field(var%name, Field2d)
     968          if (prt_level >= 10) then
     969             write(lunout,*)'Dans iophy histwrite2D,var%name apres xios_send ',&
     970                             trim(var%name)                       
     971          endif
     972#else
     973        CALL abort_gcm ('iophy','cannot have ok_all_xml = .T. without CPP_XIOS defined' ,1)
     974#endif
     975      ELSE 
     976        DO iff=iff_beg, iff_end
    947977            IF (var%flag(iff) <= lev_files(iff) .AND. clef_files(iff)) THEN
    948978
     
    10011031                deallocate(fieldok)
    10021032            ENDIF !levfiles
    1003       ENDDO ! of DO iff=iff_beg, iff_end
     1033        ENDDO ! of DO iff=iff_beg, iff_end
     1034      ENDIF
    10041035!$OMP END MASTER   
    10051036  ENDIF ! vars_defined
     
    10261057  INCLUDE 'dimensions.h'
    10271058  INCLUDE 'iniprint.h'
     1059  include 'clesphys.h'
    10281060
    10291061    TYPE(ctrl_out), INTENT(IN) :: var
     
    10781110! BOUCLE SUR LES FICHIERS
    10791111     firstx=.true.
     1112
     1113      IF (ok_all_xml) THEN
     1114#ifdef CPP_XIOS
     1115          if (prt_level >= 10) then
     1116             write(lunout,*)'Dans iophy histwrite3D,var%name ',&
     1117                             trim(var%name)                       
     1118          endif
     1119          CALL xios_send_field(var%name, Field3d)
     1120#else
     1121        CALL abort_gcm ('iophy','cannot have ok_all_xml = .T. without CPP_XIOS defined' ,1)
     1122#endif
     1123      ELSE 
     1124
     1125
    10801126     DO iff=iff_beg, iff_end
    10811127            IF (var%flag(iff) <= lev_files(iff) .AND. clef_files(iff)) THEN
     
    11361182            ENDIF
    11371183      ENDDO
     1184      ENDIF
    11381185!$OMP END MASTER   
    11391186  ENDIF ! vars_defined
Note: See TracChangeset for help on using the changeset viewer.