Changes in src/readwind_gfs.f90 [db91eb7:6ecb30a] in flexpart.git


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/readwind_gfs.f90

    rdb91eb7 r6ecb30a  
    1 
     1!**********************************************************************
    22! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
    33! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
     
    108108  character(len=24) :: gribErrorMsg = 'Error reading grib file'
    109109  character(len=20) :: gribFunction = 'readwind_gfs'
    110   character(len=20) :: shortname
    111110
    112111
     
    121120
    122121  !HSO
    123   call grib_open_file(ifile,path(3)(1:length(3)) &
     1225   call grib_open_file(ifile,path(3)(1:length(3)) &
    124123         //trim(wfname(indj)),'r',iret)
    125124  if (iret.ne.GRIB_SUCCESS) then
     
    163162
    164163  !read the grib2 identifiers
    165   call grib_get_string(igrib,'shortName',shortname,iret)
    166 
    167164  call grib_get_int(igrib,'discipline',discipl,iret)
    168165!  call grib_check(iret,gribFunction,gribErrorMsg)
     
    176173       valSurf,iret)
    177174!  call grib_check(iret,gribFunction,gribErrorMsg)
    178  
    179 !  write(*,*) 'Field: ',ifield,parCat,parNum,typSurf,shortname
     175
    180176  !convert to grib1 identifiers
    181177  isec1(6)=-1
     
    218214    isec1(7)=105         ! indicatorOfTypeOfLevel
    219215    isec1(8)=10
    220   elseif ((parCat.eq.1).and.(parNum.eq.22).and.(typSurf.eq.100)) then ! CLWMR Cloud Mixing Ratio [kg/kg]:
    221     isec1(6)=153         ! indicatorOfParameter
    222     isec1(7)=100         ! indicatorOfTypeOfLevel
    223     isec1(8)=valSurf/100 ! level, convert to hPa
    224216  elseif ((parCat.eq.3).and.(parNum.eq.1).and.(typSurf.eq.101)) then ! SLP
    225217    isec1(6)=2           ! indicatorOfParameter
     
    556548        endif
    557549      endif
    558 ! SEC & IP 12/2018 read GFS clouds
    559       if(isec1(6).eq.153) then  !! CLWCR  Cloud liquid water content [kg/kg]
    560         clwch(i,j,nlev_ec-k+2,n)=zsec4(nxfield*(ny-j-1)+i+1)
    561         readclouds=.true.
    562         sumclouds=.true.
    563       endif
    564 
    565550
    566551    end do
     
    690675    call shift_field(vvh,nxfield,ny,nuvzmax,nuvz,1,1)
    691676    call shift_field(wwh,nxfield,ny,nwzmax,nwz,1,1)
    692 ! IP & SEC adding GFS Clouds 20181205
    693     call shift_field(clwch,nxfield,ny,nuvzmax,nuvz,2,n)
    694677  endif
    695678
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG