Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/src/gridcheck_nests.f90

    r27 r4  
    4848  integer :: igrib
    4949  integer :: gribVer,parCat,parNum,typSurf,valSurf,discipl
    50   integer :: parID !added by mc for making it consistent with new gridcheck.f90
    5150  integer :: gotGrib
    5251  !HSO  end
     
    5655  real(kind=4) :: xaux1,xaux2,yaux1,yaux2
    5756  real(kind=8) :: xaux1in,xaux2in,yaux1in,yaux2in
    58   real :: conversion_factor !added by mc to make it consistent with new gridchek.f90
    5957
    6058  ! VARIABLES AND ARRAYS NEEDED FOR GRIB DECODING
     
    152150  call grib_get_int(igrib,'level',valSurf,iret)
    153151  call grib_check(iret,gribFunction,gribErrorMsg)
    154   call grib_get_int(igrib,'paramId',parId,iret) !added by mc to make it consisitent with new grid_check.f90
    155   call grib_check(iret,gribFunction,gribErrorMsg) !added by mc to make it consisitent with new  grid_check.f90
    156152
    157153  !print*,discipl,parCat,parNum,typSurf,valSurf
     
    174170  elseif ((parCat.eq.2).and.(parNum.eq.32)) then ! W, actually eta dot
    175171    isec1(6)=135         ! indicatorOfParameter
    176   elseif ((parCat.eq.128).and.(parNum.eq.77)) then ! W, actually eta dot !added bymc to make it consistent with new gridchek.f90
    177     isec1(6)=135         ! indicatorOfParameter    !                     ! " " " " " " " " " " " " " " " " " " " " " " " "  " " "
    178172  elseif ((parCat.eq.3).and.(parNum.eq.0).and.(typSurf.eq.101)) then !SLP
    179173    isec1(6)=151         ! indicatorOfParameter
     
    188182  elseif ((parCat.eq.1).and.(parNum.eq.11).and.(typSurf.eq.1)) then ! SD
    189183    isec1(6)=141         ! indicatorOfParameter
    190   elseif ((parCat.eq.6).and.(parNum.eq.1) .or. parId .eq. 164) then ! CC !added by mc to make it consistent with new gridchek.f90
     184  elseif ((parCat.eq.6).and.(parNum.eq.1)) then ! CC
    191185    isec1(6)=164         ! indicatorOfParameter
    192  elseif ((parCat.eq.1).and.(parNum.eq.9) .or. parId .eq. 142) then ! LSP !added by mc to make it consistent with new gridchek.f90
     186  elseif ((parCat.eq.1).and.(parNum.eq.9)) then ! LSP
    193187    isec1(6)=142         ! indicatorOfParameter
    194188  elseif ((parCat.eq.1).and.(parNum.eq.10)) then ! CP
     
    198192  elseif ((parCat.eq.4).and.(parNum.eq.9).and.(typSurf.eq.1)) then ! SR
    199193    isec1(6)=176         ! indicatorOfParameter
    200   elseif ((parCat.eq.2).and.(parNum.eq.17) .or. parId .eq. 180) then ! EWSS !added by mc to make it consistent with new gridchek.f90
     194  elseif ((parCat.eq.2).and.(parNum.eq.17)) then ! EWSS
    201195    isec1(6)=180         ! indicatorOfParameter
    202   elseif ((parCat.eq.2).and.(parNum.eq.18) .or. parId .eq. 181) then ! NSSS !added by mc to make it consistent with new gridchek.f90
     196  elseif ((parCat.eq.2).and.(parNum.eq.18)) then ! NSSS
    203197    isec1(6)=181         ! indicatorOfParameter
    204198  elseif ((parCat.eq.3).and.(parNum.eq.4)) then ! ORO
    205199    isec1(6)=129         ! indicatorOfParameter
    206   elseif ((parCat.eq.3).and.(parNum.eq.7) .or. parId .eq. 160) then ! SDO !added by mc to make it consistent with new gridchek.f90
     200  elseif ((parCat.eq.3).and.(parNum.eq.7)) then ! SDO
    207201    isec1(6)=160         ! indicatorOfParameter
    208202  elseif ((discipl.eq.2).and.(parCat.eq.0).and.(parNum.eq.0).and. &
     
    213207         parCat,parNum,typSurf
    214208  endif
    215   if(parId .ne. isec1(6) .and. parId .ne. 77) then !added by mc to make it consistent with new gridchek.f90
    216     write(*,*) 'parId',parId, 'isec1(6)',isec1(6)
    217 !    stop
    218   endif
    219209
    220210  endif
     
    247237
    248238  !HSO  get the second part of the grid dimensions only from GRiB1 messages
    249   if (isec1(6) .eq. 167 .and. (gotGrib.eq.0)) then !added by mc to make it consistent with new gridchek.f90 note that gotGrid must be changed in gotGrib!!
    250     call grib_get_real8(igrib,'longitudeOfFirstGridPointInDegrees', & !comment by mc: note that this was in the (if (ifield.eq.1) ..end above in gridchek.f90 see line 257
     239  if ((gribVer.eq.1).and.(gotGrib.eq.0)) then
     240    call grib_get_real8(igrib,'longitudeOfFirstGridPointInDegrees', &
    251241         xaux1in,iret)
    252242    call grib_check(iret,gribFunction,gribErrorMsg)
     
    264254    yaux1=yaux1in
    265255    yaux2=yaux2in
    266     if(xaux1.gt.180.) xaux1=xaux1-360.0
    267     if(xaux2.gt.180.) xaux2=xaux2-360.0
    268     if(xaux1.lt.-180.) xaux1=xaux1+360.0
    269     if(xaux2.lt.-180.) xaux2=xaux2+360.0
    270     if (xaux2.lt.xaux1) xaux2=xaux2+360.0
     256    if(xaux1.gt.180) xaux1=xaux1-360.0
     257    if(xaux2.gt.180) xaux2=xaux2-360.0
     258    if(xaux1.lt.-180) xaux1=xaux1+360.0
     259    if(xaux2.lt.-180) xaux2=xaux2+360.0
     260    if (xaux2.lt.xaux1) xaux2=xaux2+360.
    271261    xlon0n(l)=xaux1
    272262    ylat0n(l)=yaux1
    273263    dxn(l)=(xaux2-xaux1)/real(nxn(l)-1)
    274264    dyn(l)=(yaux2-yaux1)/real(nyn(l)-1)
    275     gotGrib=1 !commetn by mc note tahthere gotGRIB is used instead of gotGrid!!!
     265    gotGrib=1
    276266  endif ! ifield.eq.1
    277267
     
    350340  !********************
    351341
    352   write(*,'(a,i2,a)') ' Nested domain ',l,':'
    353   write(*,'(a,f10.5,a,f10.5,a,f10.5)') '  Longitude range: ', &
     342  write(*,'(a,i2)') 'Nested domain #: ',l
     343  write(*,'(a,f10.2,a1,f10.2,a,f10.2)') '  Longitude range: ', &
    354344       xlon0n(l),' to ',xlon0n(l)+(nxn(l)-1)*dxn(l), &
    355345       '   Grid distance: ',dxn(l)
    356   write(*,'(a,f10.5,a,f10.5,a,f10.5)') '  Latitude range : ', &
     346  write(*,'(a,f10.2,a1,f10.2,a,f10.2)') '  Latitude range: ', &
    357347       ylat0n(l),' to ',ylat0n(l)+(nyn(l)-1)*dyn(l), &
    358348       '   Grid distance: ',dyn(l)
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG