Ignore:
Timestamp:
Nov 28, 2014, 4:36:29 PM (11 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes -r2070:2158 into testing branch. Compilation problems introduced by revision r2155 have been corrected by hand

Location:
LMDZ5/branches/testing
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/cosp/cosp_constants.F90

    r1910 r2160  
    3131!
    3232MODULE MOD_COSP_CONSTANTS
    33 !    use netcdf, only: nf90_fill_rea
     33    use netcdf, only: nf90_fill_real
    3434    IMPLICIT NONE
    3535   
     
    4747    ! Missing value
    4848!!    real,parameter :: R_UNDEF = -1.0E30
    49      real,parameter :: R_UNDEF = 9.96921e+36
    50 !      real,parameter :: R_UNDEF = nf90_fill_rea
     49!     real,parameter :: R_UNDEF = 9.96921e+36
     50      real,parameter :: R_UNDEF = nf90_fill_real
     51
    5152    ! Number of possible output variables
    5253    integer,parameter :: N_OUT_LIST = 27
  • LMDZ5/branches/testing/libf/cosp/cosp_output_mod.F90

    r1999 r2160  
    1717      INTEGER, DIMENSION(3), SAVE  :: nhoricosp, nvert, nvertmcosp, nvertcol, nvertisccp, nvertp
    1818      REAL, DIMENSION(3), SAVE                :: zoutm_cosp
    19 !$OMP THREADPRIVATE(nhori, nvert, nvertmcosp, nvertcol, nvertisccp, nvertp, zoutm_cosp)
     19!$OMP THREADPRIVATE(nhoricosp, nvert, nvertmcosp, nvertcol, nvertisccp, nvertp, zoutm_cosp)
    2020      REAL, SAVE                   :: zdtimemoy_cosp
    2121!$OMP THREADPRIVATE(zdtimemoy_cosp)
     
    7878           by the ISCCP Simulator","K", (/ ('', i=1, 3) /))
    7979
    80 !   LOGICAL, SAVE :: cosp_varsdefined = .FALSE. ! ug PAS THREADPRIVATE ET C'EST NORMAL
    81   LOGICAL, SAVE        :: cosp_varsdefined
    82   INTEGER, save        :: Nlevout,Ncolout
    83 !$OMP THREADPRIVATE(Nlevout)
     80   LOGICAL, SAVE :: cosp_varsdefined = .FALSE. ! ug PAS THREADPRIVATE ET C'EST NORMAL
    8481
    8582CONTAINS
     
    9188
    9289  SUBROUTINE cosp_output_open(Nlevlmdz, Ncolumns, presnivs, dtime, freq_cosp, &
    93                               ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP, &
     90                              ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP, ok_all_xml,  &
    9491                              ecrit_mth, ecrit_day, ecrit_hf, use_vgrid, vgrid)
    9592
     
    110107  real,dimension(Nlevlmdz) :: presnivs
    111108  real                     :: dtime, freq_cosp, ecrit_day, ecrit_hf, ecrit_mth
    112   logical                  :: ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP, use_vgrid                   
     109  logical                  :: ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP, use_vgrid, ok_all_xml                   
    113110  type(cosp_vgrid)   :: vgrid   ! Information on vertical grid of stats
    114111
    115112!!! Variables locales
    116113  integer                  :: idayref, iff, ii
    117   real                     :: zjulian
     114  real                     :: zjulian,zjulian_start
    118115  real,dimension(Ncolumns) :: column_ax
     116  CHARACTER(LEN=20), DIMENSION(3)  :: chfreq = (/ '1day', '1d', '3h' /)           
    119117
    120118!!! Variables d'entree
     
    126124    INTEGER :: x_an, x_mois, x_jour
    127125    REAL :: x_heure
     126    INTEGER :: ini_an, ini_mois, ini_jour
     127    REAL :: ini_heure
    128128#endif
    129129
    130130    WRITE(lunout,*) 'Debut cosp_output_mod.F90'
     131    print*,'cosp_varsdefined',cosp_varsdefined
    131132    ! Initialisations (Valeurs par defaut)
    132     Nlevout = vgrid%Nlvgrid
    133     Ncolout = Ncolumns
    134133
    135134    do ii=1,Ncolumns
     
    158157    CALL getin('cosp_outfilenames',cosp_outfilenames)
    159158    CALL getin('cosp_outfilekeys',cosp_outfilekeys)
    160     CALL getin('cosp_outfiletimesteps',cosp_ecritfiles)
     159    CALL getin('cosp_ecritfiles',cosp_ecritfiles)
    161160    CALL getin('cosp_outfiletypes',cosp_outfiletypes)
    162161
    163162    WRITE(lunout,*)'cosp_outfilenames=',cosp_outfilenames
    164163    WRITE(lunout,*)'cosp_outfilekeys=',cosp_outfilekeys
    165     WRITE(lunout,*)'cosp_outfiletimesteps=',cosp_ecritfiles
     164    WRITE(lunout,*)'cosp_ecritfiles=',cosp_ecritfiles
    166165    WRITE(lunout,*)'cosp_outfiletypes=',cosp_outfiletypes
    167  
    168 #ifdef CPP_XIOS
    169     ! ug Réglage du calendrier xios
     166   
     167    idayref = day_ref
     168    CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
     169    CALL ymds2ju(annee_ref, 1, day_ini, start_time, zjulian_start)
     170
     171#ifdef CPP_XIOS
     172    ! ug R\'eglage du calendrier xios
    170173    !Temps julian => an, mois, jour, heure
    171     CALL ymds2ju(annee_ref, 1, day_ref, 0.0, zjulian)
    172174    CALL ju2ymds(zjulian, x_an, x_mois, x_jour, x_heure)
    173     CALL wxios_set_cal(dtime, calend, x_an, x_mois, x_jour, x_heure)
     175    CALL ju2ymds(zjulian_start, ini_an, ini_mois, ini_jour, ini_heure)
     176    CALL wxios_set_cal(dtime, calend, x_an, x_mois, x_jour, x_heure, ini_an, &
     177                       ini_mois, ini_jour, ini_heure )
     178       ! ug d�claration des axes verticaux de chaque fichier:
     179    if (use_vgrid) then
     180        CALL wxios_add_vaxis("height", vgrid%Nlvgrid, vgrid%z)
     181    else
     182         WRITE(lunout,*) 'wxios_add_vaxis "presnivs", vgrid%Nlvgrid ',vgrid%Nlvgrid
     183        CALL wxios_add_vaxis("presnivs", vgrid%Nlvgrid, presnivs)
     184    endif
     185    WRITE(lunout,*) 'wxios_add_vaxis height_mlev, Nlevlmdz ',Nlevlmdz
     186    CALL wxios_add_vaxis("height_mlev", Nlevlmdz, vgrid%mz)
     187    WRITE(lunout,*) 'wxios_add_vaxis sza, PARASOL_NREFL ',PARASOL_NREFL
     188    CALL wxios_add_vaxis("sza", PARASOL_NREFL, PARASOL_SZA)
     189    WRITE(lunout,*) 'wxios_add_vaxis pressure2 ',7
     190    CALL wxios_add_vaxis("pressure2", 7, ISCCP_PC)
     191    WRITE(lunout,*) 'wxios_add_vaxis column ',Ncolumns
     192    CALL wxios_add_vaxis("column", Ncolumns, column_ax)
    174193#endif
    175194   
     
    180199
    181200       IF (cosp_outfilekeys(iff)) THEN
    182            idayref = day_ref
    183            CALL ymds2ju(annee_ref, 1, idayref, 0., zjulian)
    184            CALL histbeg_phy(cosp_outfilenames(iff),itau_phy,zjulian,&
     201           CALL histbeg_phy_all(cosp_outfilenames(iff),itau_phy,zjulian,&
    185202             dtime,nhoricosp(iff),cosp_nidfiles(iff))
    186 
     203           print*,'histbeg_phy nhoricosp(iff),cosp_nidfiles(iff)', &
     204                    nhoricosp(iff),cosp_nidfiles(iff)
     205
     206#ifdef CPP_XIOS
     207        IF (.not. ok_all_xml) then
     208         WRITE(lunout,*) 'wxios_add_file ',cosp_outfilenames(iff)
     209         CALL wxios_add_file(cosp_outfilenames(iff),chfreq(iff),10)
     210        ENDIF
     211#endif
     212
     213#ifndef CPP_IOIPSL_NO_OUTPUT
    187214! Definition de l'axe vertical
    188215       if (use_vgrid) then
    189216! Axe vertical Cosp 40 niveaux (en m)
    190       CALL histvert(cosp_nidfiles(iff),"height","height","m",Nlevout,vgrid%z,nvert(iff))
     217      CALL histvert(cosp_nidfiles(iff),"height","height","m",vgrid%Nlvgrid,vgrid%z,nvert(iff))
    191218       else
    192219! Axe vertical modele LMDZ presnivs
    193       CALL histvert(cosp_nidfiles(iff),"presnivs","Vertical levels","Pa",Nlevout,presnivs,nvert(iff),"down")
     220      CALL histvert(cosp_nidfiles(iff),"presnivs","Vertical levels","Pa",vgrid%Nlvgrid,presnivs,nvert(iff),"down")
    194221       endif
    195222! Axe vertical niveaux modele (en m)
     
    201228
    202229      CALL histvert(cosp_nidfiles(iff),"column","column","count",Ncolumns,column_ax(1:Ncolumns),nvertcol(iff))
    203 
    204 #ifdef CPP_XIOS
    205     ! ug déclaration des axes verticaux de chaque fichier:
    206     if (use_vgrid) then
    207       CALL wxios_add_vaxis("height", cosp_outfilenames(iff), Nlevout, vgrid%z)
    208     else
    209       CALL wxios_add_vaxis("presnivs", cosp_outfilenames(iff), Nlevout, presnivs)
    210     endif
    211     CALL wxios_add_vaxis("height_mlev", cosp_outfilenames(iff), Nlevlmdz, vgrid%mz)
    212     CALL wxios_add_vaxis("sza", cosp_outfilenames(iff), PARASOL_NREFL, PARASOL_SZA)
    213     CALL wxios_add_vaxis("pressure2", cosp_outfilenames(iff), 7, ISCCP_PC)
    214     CALL wxios_add_vaxis("column", cosp_outfilenames(iff), Ncolumns, column_ax)
    215230#endif
    216231
  • LMDZ5/branches/testing/libf/cosp/cosp_output_write_mod.F90

    r1999 r2160  
    88   INTEGER, SAVE  :: itau_iocosp
    99!$OMP THREADPRIVATE(itau_iocosp)
     10   INTEGER, save        :: Nlevout, Ncolout
     11!$OMP THREADPRIVATE(Nlevout, Ncolout)
    1012
    1113!  INTERFACE histwrite_cosp
     
    1517   CONTAINS
    1618
    17   SUBROUTINE cosp_output_write(Nlevlmdz, Npoints, Ncolumns, itap, dtime, freq_COSP, cfg, gbx, sglidar, stlidar, isccp)
     19  SUBROUTINE cosp_output_write(Nlevlmdz, Npoints, Ncolumns, itap, dtime, freq_COSP, &
     20                               cfg, gbx, vgrid, sglidar, stlidar, isccp)
    1821
    1922    USE ioipsl
     
    2124
    2225#ifdef CPP_XIOS
    23     ! ug Pour les sorties XIOS
    24     USE wxios
     26    USE wxios, only: wxios_closedef
     27    USE xios, only: xios_update_calendar
    2528#endif
    2629
     
    3336  type(cosp_isccp)      :: isccp   ! Output from ISCCP simulator
    3437  type(cosp_lidarstats) :: stlidar ! Summary statistics from lidar simulator
     38  type(cosp_vgrid)      :: vgrid   ! Information on vertical grid of stats
    3539
    3640!!! Variables locales
    37   integer               :: icl, iinitend=1
     41  integer               :: icl
    3842  logical               :: ok_sync
    3943  integer               :: itau_wcosp
     
    4145
    4246  include "temps.h"
    43 
    44   IF (MOD(itap,NINT(freq_COSP/dtime)).EQ.0) THEN
    45        
     47  include "iniprint.h"
     48
     49  Nlevout = vgrid%Nlvgrid
     50  Ncolout = Ncolumns
     51
    4652! A refaire
    4753       itau_wcosp = itau_phy + itap + start_time * day_step / iphysiq
     54        if (prt_level >= 10) then
     55             WRITE(lunout,*)'itau_wcosp, itap, start_time, day_step, iphysiq =', &
     56                             itau_wcosp, itap, start_time, day_step, iphysiq
     57        endif
    4858
    4959! On le donne a  cosp_output_write_mod pour que les histwrite y aient acces:
    5060       CALL set_itau_iocosp(itau_wcosp)
     61        if (prt_level >= 10) then
     62              WRITE(lunout,*)'itau_iocosp =',itau_iocosp
     63        endif
    5164
    5265    ok_sync = .TRUE.
    5366   
    54     IF(.NOT.cosp_varsdefined) THEN
    55         iinitend = 2
    56     ELSE
    57         iinitend = 1
    58     ENDIF
    59 
    60 ! ug la boucle qui suit ne sert qu'une fois, pour l'initialisation, sinon il n'y a toujours qu'un seul passage:
    61 DO iinit=1, iinitend
    62 #ifdef CPP_XIOS
     67!DO iinit=1, iinitend
     68! AI sept 2014 cette boucle supprimee
     69! On n'ecrit pas quand itap=1 (cosp)
     70
     71   if (prt_level >= 10) then
     72         WRITE(lunout,*)'DO iinit=1, iinitend ',iinitend
     73   endif
     74
     75#ifdef CPP_XIOS
     76 !$OMP MASTER
    6377IF (cosp_varsdefined) THEN
    64      CALL wxios_update_calendar(itau_iocosp)
    65 END IF
     78   if (prt_level >= 10) then
     79         WRITE(lunout,*)'Apell xios_update_calendar cosp_varsdefined iinitend ', &
     80                         cosp_varsdefined,iinitend
     81   endif
     82    CALL xios_update_calendar(itau_wcosp)
     83ENDIF
     84  !$OMP END MASTER
     85  !$OMP BARRIER
    6686#endif
    6787
    6888 if (cfg%Llidar_sim) then
    69 
    7089! Pb des valeurs indefinies, on les met a 0
    7190! A refaire proprement
     
    109128   enddo
    110129
     130   print*,'Appel histwrite2d_cosp'
    111131   CALL histwrite2d_cosp(o_cllcalipso,stlidar%cldlayer(:,1))
    112132   CALL histwrite2d_cosp(o_clhcalipso,stlidar%cldlayer(:,3))
     
    201221 IF(.NOT.cosp_varsdefined) THEN
    202222!$OMP MASTER
     223#ifndef CPP_IOIPSL_NO_OUTPUT
    203224            DO iff=1,3
    204225                IF (cosp_outfilekeys(iff)) THEN
     
    206227                ENDIF ! cosp_outfilekeys
    207228            ENDDO !  iff
    208 #ifdef CPP_XIOS
     229#endif
     230! Fermeture dans phys_output_write
     231!#ifdef CPP_XIOS
    209232            !On finalise l'initialisation:
    210             CALL wxios_closedef()
    211 #endif
     233            !CALL wxios_closedef()
     234!#endif
     235
    212236!$OMP END MASTER
    213237!$OMP BARRIER
    214238            cosp_varsdefined = .TRUE.
    215239 END IF
    216 END DO  !! iinit
    217 
    218 !    IF(cosp_varsdefined) THEN
     240
     241    IF(cosp_varsdefined) THEN
    219242! On synchronise les fichiers pour IOIPSL
     243#ifndef CPP_IOIPSL_NO_OUTPUT
    220244!$OMP MASTER
    221    DO iff=1,3
     245     DO iff=1,3
    222246         IF (ok_sync .AND. cosp_outfilekeys(iff)) THEN
    223247             CALL histsync(cosp_nidfiles(iff))
    224248         ENDIF
    225    END DO
     249     END DO
    226250!$OMP END MASTER
    227 
    228    ENDIF ! if freq_COSP
     251#endif
     252    ENDIF  !cosp_varsdefined
    229253
    230254    END SUBROUTINE cosp_output_write
     
    251275    INCLUDE "dimensions.h"
    252276    INCLUDE "temps.h"
     277    INCLUDE "clesphys.h"
     278    include "iniprint.h"
    253279
    254280    INTEGER                          :: iff
     
    279305
    280306#ifdef CPP_XIOS
     307     IF (.not. ok_all_xml) then
     308       IF ( var%cles(iff) ) THEN
     309         if (prt_level >= 10) then
     310              WRITE(lunout,*)'Appel wxios_add_field_to_file var%name =',var%name
     311         endif
    281312        CALL wxios_add_field_to_file(var%name, 2, cosp_nidfiles(iff), cosp_outfilenames(iff), &
    282         var%description, var%unit, 1, typeecrit)
    283 #endif
     313                                     var%description, var%unit, 1, typeecrit)
     314       ENDIF
     315     ENDIF
     316#endif
     317
     318#ifndef CPP_IOIPSL_NO_OUTPUT
    284319       IF ( var%cles(iff) ) THEN
    285320          CALL histdef (cosp_nidfiles(iff), var%name, var%description, var%unit, &
     
    287322               typeecrit, zstophym,zoutm_cosp(iff))
    288323       ENDIF
     324#endif
    289325
    290326  END SUBROUTINE histdef2d_cosp
     
    305341    INCLUDE "dimensions.h"
    306342    INCLUDE "temps.h"
     343    INCLUDE "clesphys.h"
     344    include "iniprint.h"
    307345
    308346    INTEGER                        :: iff, klevs
     
    315353    CHARACTER(LEN=20) :: nom
    316354    character(len=2) :: str2
     355    CHARACTER(len=20) :: nam_axvert
    317356
    318357! Axe vertical
    319358      IF (nvertsave.eq.nvertp(iff)) THEN
    320359          klevs=PARASOL_NREFL
     360          nam_axvert="sza"
    321361      ELSE IF (nvertsave.eq.nvertisccp(iff)) THEN
    322362          klevs=7
     363          nam_axvert="pressure2"
    323364      ELSE IF (nvertsave.eq.nvertcol(iff)) THEN
    324365          klevs=Ncolout
     366          nam_axvert="column"
    325367      ELSE
    326           klevs=Nlevout
     368           klevs=Nlevout
     369           nam_axvert="presnivs"
    327370      ENDIF
    328      
    329          
     371
    330372! ug RUSTINE POUR LES Champs 4D
    331373      IF (PRESENT(ncols)) THEN
     
    358400
    359401#ifdef CPP_XIOS
    360         CALL wxios_add_field_to_file(nom, 3, cosp_nidfiles(iff), cosp_outfilenames(iff), &
    361         var%description, var%unit, 1, typeecrit)
    362 #endif
     402      IF (.not. ok_all_xml) then
     403        IF ( var%cles(iff) ) THEN
     404          if (prt_level >= 10) then
     405              WRITE(lunout,*)'Appel wxios_add_field_to_file 3d nom variable nam_axvert = ',nom, nam_axvert
     406          endif
     407          CALL wxios_add_field_to_file(nom, 3, cosp_nidfiles(iff), cosp_outfilenames(iff), &
     408                                       var%description, var%unit, 1, typeecrit, nam_axvert)
     409        ENDIF
     410      ENDIF
     411#endif
     412
     413#ifndef CPP_IOIPSL_NO_OUTPUT
    363414       IF ( var%cles(iff) ) THEN
    364415          CALL histdef (cosp_nidfiles(iff), nom, var%description, var%unit, &
     
    367418               zstophym, zoutm_cosp(iff))
    368419       ENDIF
     420#endif
     421
    369422  END SUBROUTINE histdef3d_cosp
    370423
     
    376429
    377430#ifdef CPP_XIOS
    378   USE wxios
     431  USE xios, only: xios_send_field
    379432#endif
    380433
     
    382435  INCLUDE 'dimensions.h'
    383436  INCLUDE 'iniprint.h'
     437  INCLUDE 'clesphys.h'
    384438
    385439    TYPE(ctrl_outcosp), INTENT(IN) :: var
     
    393447    CHARACTER(LEN=20) ::  nomi, nom
    394448    character(len=2) :: str2
     449    LOGICAL, SAVE  :: firstx
     450!$OMP THREADPRIVATE(firstx)
    395451
    396452    IF (prt_level >= 9) WRITE(lunout,*)'Begin histrwrite2d ',var%name
     
    417473
    418474! La boucle sur les fichiers:
     475      firstx=.true.
    419476      DO iff=1, 3
    420477           IF (var%cles(iff) .AND. cosp_outfilekeys(iff)) THEN
    421478                ALLOCATE(index2d(iim*jj_nb))
     479#ifndef CPP_IOIPSL_NO_OUTPUT
    422480        CALL histwrite(cosp_nidfiles(iff),var%name,itau_iocosp,Field2d,iim*jj_nb,index2d)
    423 #ifdef CPP_XIOS
    424                 IF (iff == 1) THEN
    425                    CALL wxios_write_2D(var%name, Field2d)
    426                 ENDIF
    427 #endif
    428 
     481#endif
    429482                deallocate(index2d)
    430            ENDIF !levfiles
    431       ENDDO
     483#ifdef CPP_XIOS
     484              IF (.not. ok_all_xml) then
     485                 if (firstx) then
     486                  if (prt_level >= 10) then
     487                    WRITE(lunout,*)'xios_send_field variable ',var%name
     488                  endif
     489                  CALL xios_send_field(var%name, Field2d)
     490                   firstx=.false.
     491                 endif
     492              ENDIF
     493#endif
     494           ENDIF
     495      ENDDO
     496
     497#ifdef CPP_XIOS
     498      IF (ok_all_xml) THEN
     499        if (prt_level >= 10) then
     500              WRITE(lunout,*)'xios_send_field variable ',var%name
     501        endif
     502       CALL xios_send_field(var%name, Field2d)
     503      ENDIF
     504#endif
     505
    432506!$OMP END MASTER   
    433507  ENDIF ! vars_defined
    434   IF (prt_level >= 9) WRITE(lunout,*)'End histrwrite2d_cosp ',nom
     508  IF (prt_level >= 9) WRITE(lunout,*)'End histrwrite2d_cosp ',var%name
    435509  END SUBROUTINE histwrite2d_cosp
    436510
     
    444518
    445519#ifdef CPP_XIOS
    446  USE WXIOS
     520  USE xios, only: xios_send_field
    447521#endif
    448522
     
    451525  INCLUDE 'dimensions.h'
    452526  INCLUDE 'iniprint.h'
     527  INCLUDE 'clesphys.h'
    453528
    454529    TYPE(ctrl_outcosp), INTENT(IN)    :: var
     
    465540    CHARACTER(LEN=20) ::  nomi, nom
    466541    character(len=2) :: str2
     542    LOGICAL, SAVE  :: firstx
     543!$OMP THREADPRIVATE(firstx)
    467544
    468545  IF (prt_level >= 9) write(lunout,*)'Begin histrwrite3d ',var%name
     
    498575    CALL grid1Dto2D_mpi(buffer_omp,field3d)
    499576
    500 
    501577! BOUCLE SUR LES FICHIERS
     578     firstx=.true.
    502579     DO iff=1, 3
    503580        IF (var%cles(iff) .AND. cosp_outfilekeys(iff)) THEN
    504581           ALLOCATE(index3d(iim*jj_nb*nlev))
     582#ifndef CPP_IOIPSL_NO_OUTPUT
    505583    CALL histwrite(cosp_nidfiles(iff),nom,itau_iocosp,Field3d,iim*jj_nb*nlev,index3d)
    506 
    507 #ifdef CPP_XIOS
    508            IF (iff == 1) THEN
    509                CALL wxios_write_3D(nom, Field3d(:,:,1:klev))
     584#endif
     585
     586#ifdef CPP_XIOS
     587          IF (.not. ok_all_xml) then
     588           IF (firstx) THEN
     589               CALL xios_send_field(nom, Field3d(:,:,1:nlev))
     590               IF (prt_level >= 9) WRITE(lunout,*)'xios_send_field ',var%name
     591               firstx=.FALSE.
    510592           ENDIF
     593          ENDIF
    511594#endif
    512595         deallocate(index3d)
    513596        ENDIF
    514597      ENDDO
     598#ifdef CPP_XIOS
     599    IF (ok_all_xml) THEN
     600     CALL xios_send_field(nom, Field3d(:,:,1:nlev))
     601     IF (prt_level >= 9) WRITE(lunout,*)'xios_send_field ',var%name
     602    ENDIF
     603#endif
     604
    515605!$OMP END MASTER   
    516606  ENDIF ! vars_defined
  • LMDZ5/branches/testing/libf/cosp/phys_cosp.F90

    r1999 r2160  
    66  subroutine phys_cosp( itap,dtime,freq_cosp, &
    77                        ok_mensuelCOSP,ok_journeCOSP,ok_hfCOSP, &
    8                         ecrit_mth,ecrit_day,ecrit_hf, &
     8                        ecrit_mth,ecrit_day,ecrit_hf, ok_all_xml, &
    99                        Nptslmdz,Nlevlmdz,lon,lat, presnivs,overlaplmdz,sunlit, &
    1010                        ref_liq,ref_ice,fracTerLic,u_wind,v_wind,phis,phi,ph,p,skt,t, &
     
    8484  character(len=64),PARAMETER  :: cosp_input_nl='cosp_input_nl.txt'
    8585  character(len=64),PARAMETER  :: cosp_output_nl='cosp_output_nl.txt'
    86   character(len=512), save :: finput ! Input file name
    87   character(len=512), save :: cmor_nl
    8886  integer, save :: isccp_topheight,isccp_topheight_direction,overlap
    8987  integer,save  :: Ncolumns     ! Number of subcolumns in SCOPS
     
    121119  integer :: ii
    122120  real    :: ecrit_day,ecrit_hf,ecrit_mth
    123   logical :: ok_mensuelCOSP,ok_journeCOSP,ok_hfCOSP
     121  logical :: ok_mensuelCOSP,ok_journeCOSP,ok_hfCOSP, ok_all_xml
    124122
    125123  logical, save :: debut_cosp=.true.
     
    140138 
    141139!
    142    namelist/COSP_INPUT/cmor_nl,overlap,isccp_topheight,isccp_topheight_direction, &
    143               npoints_it,ncolumns,nlevels,use_vgrid,nlr,csat_vgrid,finput, &
     140   namelist/COSP_INPUT/overlap,isccp_topheight,isccp_topheight_direction, &
     141              npoints_it,ncolumns,use_vgrid,nlr,csat_vgrid, &
    144142              radar_freq,surface_radar,use_mie_tables, &
    145143              use_gas_abs,do_ray,melt_lay,k2,Nprmts_max_hydro,Naero,Nprmts_max_aero, &
     
    297295     if (debut_cosp) then
    298296
     297      !$OMP MASTER
    299298        print *, ' Open outpts files and define axis'
    300299        call cosp_output_open(Nlevlmdz, Ncolumns, presnivs, dtime, freq_cosp, &
    301                               ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP, &
     300                              ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP, ok_all_xml, &
    302301                              ecrit_mth, ecrit_day, ecrit_hf, use_vgrid, vgrid)
    303 
     302      !$OMP END MASTER
     303      !$OMP BARRIER
    304304        debut_cosp=.false.
    305305      endif ! debut_cosp
     
    313313!!!!!!!!!!!!!!!!!! Ecreture des sorties Cosp !!!!!!!!!!!!!!r!!!!!!:!!!!!
    314314       print *, 'Calling write output'
    315         call cosp_output_write(Nlevlmdz, Npoints, Ncolumns, itap, dtime, freq_COSP, cfg, gbx, sglidar, stlidar, isccp)
     315        call cosp_output_write(Nlevlmdz, Npoints, Ncolumns, itap, dtime, freq_COSP, &
     316                               cfg, gbx, vgrid, sglidar, stlidar, isccp)
    316317
    317318!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
     
    343344      CLOSE(10)
    344345    ENDIF
    345     CALL bcast(cmor_nl)
    346346    CALL bcast(overlap)
    347347    CALL bcast(isccp_topheight)
     
    349349    CALL bcast(npoints_it)
    350350    CALL bcast(ncolumns)
    351     CALL bcast(nlevels)
    352351    CALL bcast(use_vgrid)
    353352    CALL bcast(nlr)
    354353    CALL bcast(csat_vgrid)
    355     CALL bcast(finput)
    356354    CALL bcast(radar_freq)
    357355    CALL bcast(surface_radar)
Note: See TracChangeset for help on using the changeset viewer.