Changeset 24 for trunk/src/gridcheck.f90


Ignore:
Timestamp:
May 23, 2014, 11:48:41 AM (10 years ago)
Author:
igpis
Message:

version 9.2 beta. Changes from HH, AST, MC, NIK, IP. Changes in vert transform. New SPECIES input includes scavenging coefficients

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/src/gridcheck.f90

    r20 r24  
    8484  real(kind=4) :: xaux1,xaux2,yaux1,yaux2
    8585  real(kind=8) :: xaux1in,xaux2in,yaux1in,yaux2in
    86   integer :: gribVer,parCat,parNum,typSurf,valSurf,discipl
     86  integer :: gribVer,parCat,parNum,typSurf,valSurf,discipl,parID
    8787  !HSO  end
    8888  integer :: ix,jy,i,ifn,ifield,j,k,iumax,iwmax,numskip
    89   real :: sizesouth,sizenorth,xauxa,pint
     89  real :: sizesouth,sizenorth,xauxa,pint,conversion_factor
    9090
    9191  ! VARIABLES AND ARRAYS NEEDED FOR GRIB DECODING
     
    9898
    9999  integer :: isec1(56),isec2(22+nxmax+nymax)
    100   !real(kind=4) :: zsec2(60+2*nuvzmax),zsec4(jpunp)
    101   real(kind=4) :: zsec2(184),zsec4(jpunp)
     100  real(kind=4) :: zsec2(60+2*nuvzmax),zsec4(jpunp)
    102101  character(len=1) :: opt
    103102
     
    172171  call grib_check(iret,gribFunction,gribErrorMsg)
    173172  call grib_get_int(igrib,'level',valSurf,iret)
     173  call grib_check(iret,gribFunction,gribErrorMsg)
     174  call grib_get_int(igrib,'paramId',parId,iret)
    174175  call grib_check(iret,gribFunction,gribErrorMsg)
    175176
     
    193194  elseif ((parCat.eq.2).and.(parNum.eq.32)) then ! W, actually eta dot
    194195    isec1(6)=135         ! indicatorOfParameter
     196  elseif ((parCat.eq.128).and.(parNum.eq.77)) then ! W, actually eta dot
     197    isec1(6)=135         ! indicatorOfParameter
    195198  elseif ((parCat.eq.3).and.(parNum.eq.0).and.(typSurf.eq.101)) then !SLP
    196199    isec1(6)=151         ! indicatorOfParameter
     
    205208  elseif ((parCat.eq.1).and.(parNum.eq.11).and.(typSurf.eq.1)) then ! SD
    206209    isec1(6)=141         ! indicatorOfParameter
    207   elseif ((parCat.eq.6).and.(parNum.eq.1)) then ! CC
     210  elseif ((parCat.eq.6).and.(parNum.eq.1) .or. parId .eq. 164) then ! CC
    208211    isec1(6)=164         ! indicatorOfParameter
    209   elseif ((parCat.eq.1).and.(parNum.eq.9)) then ! LSP
     212  elseif ((parCat.eq.1).and.(parNum.eq.9) .or. parId .eq. 142) then ! LSP
    210213    isec1(6)=142         ! indicatorOfParameter
    211214  elseif ((parCat.eq.1).and.(parNum.eq.10)) then ! CP
     
    215218  elseif ((parCat.eq.4).and.(parNum.eq.9).and.(typSurf.eq.1)) then ! SR
    216219    isec1(6)=176         ! indicatorOfParameter
    217   elseif ((parCat.eq.2).and.(parNum.eq.17)) then ! EWSS
     220  elseif ((parCat.eq.2).and.(parNum.eq.17) .or. parId .eq. 180) then ! EWSS
    218221    isec1(6)=180         ! indicatorOfParameter
    219   elseif ((parCat.eq.2).and.(parNum.eq.18)) then ! NSSS
     222  elseif ((parCat.eq.2).and.(parNum.eq.18) .or. parId .eq. 181) then ! NSSS
    220223    isec1(6)=181         ! indicatorOfParameter
    221224  elseif ((parCat.eq.3).and.(parNum.eq.4)) then ! ORO
    222225    isec1(6)=129         ! indicatorOfParameter
    223   elseif ((parCat.eq.3).and.(parNum.eq.7)) then ! SDO
     226  elseif ((parCat.eq.3).and.(parNum.eq.7) .or. parId .eq. 160) then ! SDO
    224227    isec1(6)=160         ! indicatorOfParameter
    225228  elseif ((discipl.eq.2).and.(parCat.eq.0).and.(parNum.eq.0).and. &
     
    230233         parCat,parNum,typSurf
    231234  endif
     235  if(parId .ne. isec1(6) .and. parId .ne. 77) then
     236    write(*,*) 'parId',parId, 'isec1(6)',isec1(6)
     237!    stop
     238  endif
    232239
    233240  endif
     
    265272
    266273  !HSO  get the second part of the grid dimensions only from GRiB1 messages
    267   if ((gribVer.eq.1).and.(gotGrid.eq.0)) then
     274  if (isec1(6) .eq. 167 .and. (gotGrid.eq.0)) then
    268275    call grib_get_real8(igrib,'longitudeOfLastGridPointInDegrees', &
    269276         xaux2in,iret)
     
    291298    dyconst=180./(dy*r_earth*pi)
    292299    gotGrid=1
    293 
    294300  ! Check whether fields are global
    295301  ! If they contain the poles, specify polar stereographic map
     
    443449  write(*,*)
    444450  write(*,'(a)') 'Mother domain:'
    445   write(*,'(a,f10.2,a1,f10.2,a,f10.2)') '  Longitude range: ', &
     451  write(*,'(a,f10.5,a,f10.5,a,f10.5)') '  Longitude range: ', &
    446452       xlon0,' to ',xlon0+(nx-1)*dx,'   Grid distance: ',dx
    447   write(*,'(a,f10.2,a1,f10.2,a,f10.2)') '  Latitude range: ', &
     453  write(*,'(a,f10.5,a,f10.5,a,f10.5)') '  Latitude range: ', &
    448454       ylat0,' to ',ylat0+(ny-1)*dy,'   Grid distance: ',dy
    449455  write(*,*)
     
    467473    k=nlev_ec+1+numskip+i
    468474    akm(nwz-i+1)=zsec2(j)
     475  !   write (*,*) 'ifield:',ifield,k,j,zsec2(10+j)
    469476    bkm(nwz-i+1)=zsec2(k)
    470477  end do
     
    553560
    554561end subroutine gridcheck
     562
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG