Changeset 2137 for LMDZ5/trunk/libf/cosp


Ignore:
Timestamp:
Oct 29, 2014, 8:47:46 PM (10 years ago)
Author:
idelkadi
Message:

Implementation de XIOS pour les sorties du simulateur COSP

Location:
LMDZ5/trunk/libf/cosp
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/cosp/cosp_output_mod.F90

    r2080 r2137  
    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
     80   LOGICAL, SAVE :: cosp_varsdefined = .FALSE. ! ug PAS THREADPRIVATE ET C'EST NORMAL
    8281
    8382CONTAINS
     
    8988
    9089  SUBROUTINE cosp_output_open(Nlevlmdz, Ncolumns, presnivs, dtime, freq_cosp, &
    91                               ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP, &
     90                              ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP, ok_all_xml,  &
    9291                              ecrit_mth, ecrit_day, ecrit_hf, use_vgrid, vgrid)
    9392
     
    108107  real,dimension(Nlevlmdz) :: presnivs
    109108  real                     :: dtime, freq_cosp, ecrit_day, ecrit_hf, ecrit_mth
    110   logical                  :: ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP, use_vgrid                   
     109  logical                  :: ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP, use_vgrid, ok_all_xml                   
    111110  type(cosp_vgrid)   :: vgrid   ! Information on vertical grid of stats
    112111
    113112!!! Variables locales
    114113  integer                  :: idayref, iff, ii
    115   real                     :: zjulian
     114  real                     :: zjulian,zjulian_start
    116115  real,dimension(Ncolumns) :: column_ax
     116  CHARACTER(LEN=20), DIMENSION(3)  :: chfreq = (/ '1day', '1d', '3h' /)           
    117117
    118118!!! Variables d'entree
     
    124124    INTEGER :: x_an, x_mois, x_jour
    125125    REAL :: x_heure
     126    INTEGER :: ini_an, ini_mois, ini_jour
     127    REAL :: ini_heure
    126128#endif
    127129
    128130    WRITE(lunout,*) 'Debut cosp_output_mod.F90'
     131    print*,'cosp_varsdefined',cosp_varsdefined
    129132    ! Initialisations (Valeurs par defaut)
    130133
     
    154157    CALL getin('cosp_outfilenames',cosp_outfilenames)
    155158    CALL getin('cosp_outfilekeys',cosp_outfilekeys)
    156     CALL getin('cosp_outfiletimesteps',cosp_ecritfiles)
     159    CALL getin('cosp_ecritfiles',cosp_ecritfiles)
    157160    CALL getin('cosp_outfiletypes',cosp_outfiletypes)
    158161
    159162    WRITE(lunout,*)'cosp_outfilenames=',cosp_outfilenames
    160163    WRITE(lunout,*)'cosp_outfilekeys=',cosp_outfilekeys
    161     WRITE(lunout,*)'cosp_outfiletimesteps=',cosp_ecritfiles
     164    WRITE(lunout,*)'cosp_ecritfiles=',cosp_ecritfiles
    162165    WRITE(lunout,*)'cosp_outfiletypes=',cosp_outfiletypes
    163  
    164 #ifdef CPP_XIOS
    165     ! 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
    166173    !Temps julian => an, mois, jour, heure
    167     CALL ymds2ju(annee_ref, 1, day_ref, 0.0, zjulian)
    168174    CALL ju2ymds(zjulian, x_an, x_mois, x_jour, x_heure)
    169     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)
    170193#endif
    171194   
     
    176199
    177200       IF (cosp_outfilekeys(iff)) THEN
    178            idayref = day_ref
    179            CALL ymds2ju(annee_ref, 1, idayref, 0., zjulian)
    180            CALL histbeg_phy(cosp_outfilenames(iff),itau_phy,zjulian,&
     201           CALL histbeg_phy_all(cosp_outfilenames(iff),itau_phy,zjulian,&
    181202             dtime,nhoricosp(iff),cosp_nidfiles(iff))
    182 
     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
    183214! Definition de l'axe vertical
    184215       if (use_vgrid) then
     
    197228
    198229      CALL histvert(cosp_nidfiles(iff),"column","column","count",Ncolumns,column_ax(1:Ncolumns),nvertcol(iff))
    199 
    200 #ifdef CPP_XIOS
    201     ! ug déclaration des axes verticaux de chaque fichier:
    202     if (use_vgrid) then
    203       CALL wxios_add_vaxis("height", cosp_outfilenames(iff), vgrid%Nlvgrid, vgrid%z)
    204     else
    205       CALL wxios_add_vaxis("presnivs", cosp_outfilenames(iff), vgrid%Nlvgrid, presnivs)
    206     endif
    207     CALL wxios_add_vaxis("height_mlev", cosp_outfilenames(iff), Nlevlmdz, vgrid%mz)
    208     CALL wxios_add_vaxis("sza", cosp_outfilenames(iff), PARASOL_NREFL, PARASOL_SZA)
    209     CALL wxios_add_vaxis("pressure2", cosp_outfilenames(iff), 7, ISCCP_PC)
    210     CALL wxios_add_vaxis("column", cosp_outfilenames(iff), Ncolumns, column_ax)
    211230#endif
    212231
  • LMDZ5/trunk/libf/cosp/cosp_output_write_mod.F90

    r2080 r2137  
    1717   CONTAINS
    1818
    19   SUBROUTINE cosp_output_write(Nlevlmdz, Npoints, Ncolumns, itap, dtime, freq_COSP, cfg, gbx, vgrid, sglidar, stlidar, isccp)
     19  SUBROUTINE cosp_output_write(Nlevlmdz, Npoints, Ncolumns, itap, dtime, freq_COSP, &
     20                               cfg, gbx, vgrid, sglidar, stlidar, isccp)
    2021
    2122    USE ioipsl
     
    2324
    2425#ifdef CPP_XIOS
    25     ! ug Pour les sorties XIOS
    26     USE wxios
     26    USE wxios, only: wxios_closedef
     27    USE xios, only: xios_update_calendar
    2728#endif
    2829
     
    3839
    3940!!! Variables locales
    40   integer               :: icl, iinitend=1
     41  integer               :: icl
    4142  logical               :: ok_sync
    4243  integer               :: itau_wcosp
     
    4445
    4546  include "temps.h"
     47  include "iniprint.h"
    4648
    4749  Nlevout = vgrid%Nlvgrid
    4850  Ncolout = Ncolumns
    4951
    50   IF (MOD(itap,NINT(freq_COSP/dtime)).EQ.0) THEN
    51        
    5252! A refaire
    5353       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
    5458
    5559! On le donne a  cosp_output_write_mod pour que les histwrite y aient acces:
    5660       CALL set_itau_iocosp(itau_wcosp)
     61        if (prt_level >= 10) then
     62              WRITE(lunout,*)'itau_iocosp =',itau_iocosp
     63        endif
    5764
    5865    ok_sync = .TRUE.
    5966   
    60     IF(.NOT.cosp_varsdefined) THEN
    61         iinitend = 2
    62     ELSE
    63         iinitend = 1
    64     ENDIF
    65 
    66 ! ug la boucle qui suit ne sert qu'une fois, pour l'initialisation, sinon il n'y a toujours qu'un seul passage:
    67 DO iinit=1, iinitend
    68 #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
    6977IF (cosp_varsdefined) THEN
    70      CALL wxios_update_calendar(itau_iocosp)
    71 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
    7286#endif
    7387
    7488 if (cfg%Llidar_sim) then
    75 ! print*,'cfg%Llidar_sim dans output_write',cfg%Llidar_sim
    76 ! print*,'Nlevout Npoints dans output_write, R_UNDEF =',Nlevout,Npoints,R_UNDEF
    7789! Pb des valeurs indefinies, on les met a 0
    7890! A refaire proprement
     
    116128   enddo
    117129
     130   print*,'Appel histwrite2d_cosp'
    118131   CALL histwrite2d_cosp(o_cllcalipso,stlidar%cldlayer(:,1))
    119132   CALL histwrite2d_cosp(o_clhcalipso,stlidar%cldlayer(:,3))
     
    208221 IF(.NOT.cosp_varsdefined) THEN
    209222!$OMP MASTER
     223#ifndef CPP_IOIPSL_NO_OUTPUT
    210224            DO iff=1,3
    211225                IF (cosp_outfilekeys(iff)) THEN
     
    213227                ENDIF ! cosp_outfilekeys
    214228            ENDDO !  iff
    215 #ifdef CPP_XIOS
     229#endif
     230! Fermeture dans phys_output_write
     231!#ifdef CPP_XIOS
    216232            !On finalise l'initialisation:
    217             CALL wxios_closedef()
    218 #endif
     233            !CALL wxios_closedef()
     234!#endif
     235
    219236!$OMP END MASTER
    220237!$OMP BARRIER
    221238            cosp_varsdefined = .TRUE.
    222239 END IF
    223 END DO  !! iinit
    224 
    225 !    IF(cosp_varsdefined) THEN
     240
     241    IF(cosp_varsdefined) THEN
    226242! On synchronise les fichiers pour IOIPSL
     243#ifndef CPP_IOIPSL_NO_OUTPUT
    227244!$OMP MASTER
    228    DO iff=1,3
     245     DO iff=1,3
    229246         IF (ok_sync .AND. cosp_outfilekeys(iff)) THEN
    230247             CALL histsync(cosp_nidfiles(iff))
    231248         ENDIF
    232    END DO
     249     END DO
    233250!$OMP END MASTER
    234 
    235    ENDIF ! if freq_COSP
     251#endif
     252    ENDIF  !cosp_varsdefined
    236253
    237254    END SUBROUTINE cosp_output_write
     
    258275    INCLUDE "dimensions.h"
    259276    INCLUDE "temps.h"
     277    INCLUDE "clesphys.h"
     278    include "iniprint.h"
    260279
    261280    INTEGER                          :: iff
     
    286305
    287306#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
    288312        CALL wxios_add_field_to_file(var%name, 2, cosp_nidfiles(iff), cosp_outfilenames(iff), &
    289         var%description, var%unit, 1, typeecrit)
    290 #endif
     313                                     var%description, var%unit, 1, typeecrit)
     314       ENDIF
     315     ENDIF
     316#endif
     317
     318#ifndef CPP_IOIPSL_NO_OUTPUT
    291319       IF ( var%cles(iff) ) THEN
    292320          CALL histdef (cosp_nidfiles(iff), var%name, var%description, var%unit, &
     
    294322               typeecrit, zstophym,zoutm_cosp(iff))
    295323       ENDIF
     324#endif
    296325
    297326  END SUBROUTINE histdef2d_cosp
     
    312341    INCLUDE "dimensions.h"
    313342    INCLUDE "temps.h"
     343    INCLUDE "clesphys.h"
     344    include "iniprint.h"
    314345
    315346    INTEGER                        :: iff, klevs
     
    322353    CHARACTER(LEN=20) :: nom
    323354    character(len=2) :: str2
     355    CHARACTER(len=20) :: nam_axvert
    324356
    325357! Axe vertical
    326358      IF (nvertsave.eq.nvertp(iff)) THEN
    327359          klevs=PARASOL_NREFL
     360          nam_axvert="sza"
    328361      ELSE IF (nvertsave.eq.nvertisccp(iff)) THEN
    329362          klevs=7
     363          nam_axvert="pressure2"
    330364      ELSE IF (nvertsave.eq.nvertcol(iff)) THEN
    331365          klevs=Ncolout
     366          nam_axvert="column"
    332367      ELSE
    333           klevs=Nlevout
     368           klevs=Nlevout
     369           nam_axvert="presnivs"
    334370      ENDIF
    335      
    336          
     371
    337372! ug RUSTINE POUR LES Champs 4D
    338373      IF (PRESENT(ncols)) THEN
     
    365400
    366401#ifdef CPP_XIOS
    367         CALL wxios_add_field_to_file(nom, 3, cosp_nidfiles(iff), cosp_outfilenames(iff), &
    368         var%description, var%unit, 1, typeecrit)
    369 #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
    370414       IF ( var%cles(iff) ) THEN
    371415          CALL histdef (cosp_nidfiles(iff), nom, var%description, var%unit, &
     
    374418               zstophym, zoutm_cosp(iff))
    375419       ENDIF
     420#endif
     421
    376422  END SUBROUTINE histdef3d_cosp
    377423
     
    383429
    384430#ifdef CPP_XIOS
    385   USE wxios
     431  USE xios, only: xios_send_field
    386432#endif
    387433
     
    389435  INCLUDE 'dimensions.h'
    390436  INCLUDE 'iniprint.h'
     437  INCLUDE 'clesphys.h'
    391438
    392439    TYPE(ctrl_outcosp), INTENT(IN) :: var
     
    400447    CHARACTER(LEN=20) ::  nomi, nom
    401448    character(len=2) :: str2
     449    LOGICAL, SAVE  :: firstx
     450!$OMP THREADPRIVATE(firstx)
    402451
    403452    IF (prt_level >= 9) WRITE(lunout,*)'Begin histrwrite2d ',var%name
     
    424473
    425474! La boucle sur les fichiers:
     475      firstx=.true.
    426476      DO iff=1, 3
    427477           IF (var%cles(iff) .AND. cosp_outfilekeys(iff)) THEN
    428478                ALLOCATE(index2d(iim*jj_nb))
     479#ifndef CPP_IOIPSL_NO_OUTPUT
    429480        CALL histwrite(cosp_nidfiles(iff),var%name,itau_iocosp,Field2d,iim*jj_nb,index2d)
    430 #ifdef CPP_XIOS
    431                 IF (iff == 1) THEN
    432                    CALL wxios_write_2D(var%name, Field2d)
    433                 ENDIF
    434 #endif
    435 
     481#endif
    436482                deallocate(index2d)
    437            ENDIF !levfiles
    438       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
    439506!$OMP END MASTER   
    440507  ENDIF ! vars_defined
    441   IF (prt_level >= 9) WRITE(lunout,*)'End histrwrite2d_cosp ',nom
     508  IF (prt_level >= 9) WRITE(lunout,*)'End histrwrite2d_cosp ',var%name
    442509  END SUBROUTINE histwrite2d_cosp
    443510
     
    451518
    452519#ifdef CPP_XIOS
    453  USE WXIOS
     520  USE xios, only: xios_send_field
    454521#endif
    455522
     
    458525  INCLUDE 'dimensions.h'
    459526  INCLUDE 'iniprint.h'
     527  INCLUDE 'clesphys.h'
    460528
    461529    TYPE(ctrl_outcosp), INTENT(IN)    :: var
     
    472540    CHARACTER(LEN=20) ::  nomi, nom
    473541    character(len=2) :: str2
     542    LOGICAL, SAVE  :: firstx
     543!$OMP THREADPRIVATE(firstx)
    474544
    475545  IF (prt_level >= 9) write(lunout,*)'Begin histrwrite3d ',var%name
     
    505575    CALL grid1Dto2D_mpi(buffer_omp,field3d)
    506576
    507 
    508577! BOUCLE SUR LES FICHIERS
     578     firstx=.true.
    509579     DO iff=1, 3
    510580        IF (var%cles(iff) .AND. cosp_outfilekeys(iff)) THEN
    511581           ALLOCATE(index3d(iim*jj_nb*nlev))
     582#ifndef CPP_IOIPSL_NO_OUTPUT
    512583    CALL histwrite(cosp_nidfiles(iff),nom,itau_iocosp,Field3d,iim*jj_nb*nlev,index3d)
    513 
    514 #ifdef CPP_XIOS
    515            IF (iff == 1) THEN
    516                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.
    517592           ENDIF
     593          ENDIF
    518594#endif
    519595         deallocate(index3d)
    520596        ENDIF
    521597      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
    522605!$OMP END MASTER   
    523606  ENDIF ! vars_defined
  • LMDZ5/trunk/libf/cosp/phys_cosp.F90

    r2080 r2137  
    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, &
     
    119119  integer :: ii
    120120  real    :: ecrit_day,ecrit_hf,ecrit_mth
    121   logical :: ok_mensuelCOSP,ok_journeCOSP,ok_hfCOSP
     121  logical :: ok_mensuelCOSP,ok_journeCOSP,ok_hfCOSP, ok_all_xml
    122122
    123123  logical, save :: debut_cosp=.true.
     
    298298        print *, ' Open outpts files and define axis'
    299299        call cosp_output_open(Nlevlmdz, Ncolumns, presnivs, dtime, freq_cosp, &
    300                               ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP, &
     300                              ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP, ok_all_xml, &
    301301                              ecrit_mth, ecrit_day, ecrit_hf, use_vgrid, vgrid)
    302302      !$OMP END MASTER
     
    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, vgrid, sglidar, stlidar, isccp)
     315        call cosp_output_write(Nlevlmdz, Npoints, Ncolumns, itap, dtime, freq_COSP, &
     316                               cfg, gbx, vgrid, sglidar, stlidar, isccp)
    316317
    317318!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Note: See TracChangeset for help on using the changeset viewer.