Changeset 4fbe7a5 in flexpart.git for src/gridcheck_nests.f90


Ignore:
Timestamp:
May 23, 2014, 11:48:41 AM (10 years ago)
Author:
Ignacio Pisso <ip@…>
Branches:
master, 10.4.1_pesei, FPv9.3.1, FPv9.3.1b_testing, FPv9.3.2, GFS_025, NetCDF, bugfixes+enhancements, deposition, dev, fp9.3.1-20161214-nc4, grib2nc4_repair, inputlist, laptop, release-10, release-10.4.1, scaling-bug, svn-petra, svn-trunk, univie
Children:
0aded10
Parents:
f13406c
Message:

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

git-svn-id: http://flexpart.flexpart.eu:8088/svn/FlexPart90/trunk@24 ef8cc7e1-21b7-489e-abab-c1baa636049d

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/gridcheck_nests.f90

    re200b7a r4fbe7a5  
    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
    5051  integer :: gotGrib
    5152  !HSO  end
     
    5556  real(kind=4) :: xaux1,xaux2,yaux1,yaux2
    5657  real(kind=8) :: xaux1in,xaux2in,yaux1in,yaux2in
     58  real :: conversion_factor !added by mc to make it consistent with new gridchek.f90
    5759
    5860  ! VARIABLES AND ARRAYS NEEDED FOR GRIB DECODING
     
    150152  call grib_get_int(igrib,'level',valSurf,iret)
    151153  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
    152156
    153157  !print*,discipl,parCat,parNum,typSurf,valSurf
     
    170174  elseif ((parCat.eq.2).and.(parNum.eq.32)) then ! W, actually eta dot
    171175    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    !                     ! " " " " " " " " " " " " " " " " " " " " " " " "  " " "
    172178  elseif ((parCat.eq.3).and.(parNum.eq.0).and.(typSurf.eq.101)) then !SLP
    173179    isec1(6)=151         ! indicatorOfParameter
     
    182188  elseif ((parCat.eq.1).and.(parNum.eq.11).and.(typSurf.eq.1)) then ! SD
    183189    isec1(6)=141         ! indicatorOfParameter
    184   elseif ((parCat.eq.6).and.(parNum.eq.1)) then ! CC
     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
    185191    isec1(6)=164         ! indicatorOfParameter
    186   elseif ((parCat.eq.1).and.(parNum.eq.9)) then ! LSP
     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
    187193    isec1(6)=142         ! indicatorOfParameter
    188194  elseif ((parCat.eq.1).and.(parNum.eq.10)) then ! CP
     
    192198  elseif ((parCat.eq.4).and.(parNum.eq.9).and.(typSurf.eq.1)) then ! SR
    193199    isec1(6)=176         ! indicatorOfParameter
    194   elseif ((parCat.eq.2).and.(parNum.eq.17)) then ! EWSS
     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
    195201    isec1(6)=180         ! indicatorOfParameter
    196   elseif ((parCat.eq.2).and.(parNum.eq.18)) then ! NSSS
     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
    197203    isec1(6)=181         ! indicatorOfParameter
    198204  elseif ((parCat.eq.3).and.(parNum.eq.4)) then ! ORO
    199205    isec1(6)=129         ! indicatorOfParameter
    200   elseif ((parCat.eq.3).and.(parNum.eq.7)) then ! SDO
     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
    201207    isec1(6)=160         ! indicatorOfParameter
    202208  elseif ((discipl.eq.2).and.(parCat.eq.0).and.(parNum.eq.0).and. &
     
    207213         parCat,parNum,typSurf
    208214  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
    209219
    210220  endif
     
    237247
    238248  !HSO  get the second part of the grid dimensions only from GRiB1 messages
    239   if ((gribVer.eq.1).and.(gotGrib.eq.0)) then
    240     call grib_get_real8(igrib,'longitudeOfFirstGridPointInDegrees', &
     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
    241251         xaux1in,iret)
    242252    call grib_check(iret,gribFunction,gribErrorMsg)
     
    254264    yaux1=yaux1in
    255265    yaux2=yaux2in
    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.
     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
    261271    xlon0n(l)=xaux1
    262272    ylat0n(l)=yaux1
    263273    dxn(l)=(xaux2-xaux1)/real(nxn(l)-1)
    264274    dyn(l)=(yaux2-yaux1)/real(nyn(l)-1)
    265     gotGrib=1
     275    gotGrib=1 !commetn by mc note tahthere gotGRIB is used instead of gotGrid!!!
    266276  endif ! ifield.eq.1
    267277
     
    341351
    342352  write(*,'(a,i2)') 'Nested domain #: ',l
    343   write(*,'(a,f10.2,a1,f10.2,a,f10.2)') '  Longitude range: ', &
     353  write(*,'(a,f10.5,a,f10.5,a,f10.5)') '  Longitude range: ', &
    344354       xlon0n(l),' to ',xlon0n(l)+(nxn(l)-1)*dxn(l), &
    345355       '   Grid distance: ',dxn(l)
    346   write(*,'(a,f10.2,a1,f10.2,a,f10.2)') '  Latitude range: ', &
     356  write(*,'(a,f10.5,a,f10.5,a,f10.5)') '  Latitude range: ', &
    347357       ylat0n(l),' to ',ylat0n(l)+(nyn(l)-1)*dyn(l), &
    348358       '   Grid distance: ',dyn(l)
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG