Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/src/readwind_nests.f90

    r24 r4  
    5151  integer :: igrib
    5252  integer :: gribVer,parCat,parNum,typSurf,valSurf,discipl
    53   integer :: parId !!added by mc for making it consistent with new readwind.f90
    5453  integer :: gotGrid
    5554  !HSO  end
     
    7069  integer :: isec1(56),isec2(22+nxmaxn+nymaxn)
    7170  real(kind=4) :: zsec4(jpunp)
    72   real(kind=4) :: xaux,yaux
    7371  real(kind=8) :: xauxin,yauxin
    74   real,parameter :: eps=1.e-4
     72  real(kind=4) :: xaux,yaux,xaux0,yaux0
    7573  real :: ewss(0:nxmaxn-1,0:nymaxn-1),nsss(0:nxmaxn-1,0:nymaxn-1)
    7674  real :: plev1,pmean,tv,fu,hlev1,ff10m,fflev1
    77   real :: conversion_factor !added by mc to make it consistent with new gridchek.f90
    7875
    7976  logical :: hflswitch,strswitch
     
    137134  endif
    138135
    139   conversion_factor=1.
    140 
    141 
    142136  else
    143137
     
    154148  call grib_get_int(igrib,'level',valSurf,iret)
    155149  call grib_check(iret,gribFunction,gribErrorMsg)
    156   call grib_get_int(igrib,'paramId',parId,iret) !added by mc to make it consisitent with new readwind.f90
    157   call grib_check(iret,gribFunction,gribErrorMsg) !added by mc to make it consisitent with new readwind.f90
    158150
    159151  !print*,discipl,parCat,parNum,typSurf,valSurf
     
    164156  isec1(8)=-1
    165157  isec1(8)=valSurf     ! level
    166    conversion_factor=1.
    167158  if ((parCat.eq.0).and.(parNum.eq.0).and.(typSurf.eq.105)) then ! T
    168159    isec1(6)=130         ! indicatorOfParameter
     
    175166  elseif ((parCat.eq.3).and.(parNum.eq.0).and.(typSurf.eq.1)) then !SP
    176167    isec1(6)=134         ! indicatorOfParameter
    177   elseif ((parCat.eq.2).and.(parNum.eq.32)) then ! W, actually eta dot !
     168  elseif ((parCat.eq.2).and.(parNum.eq.32)) then ! W, actually eta dot
    178169    isec1(6)=135         ! indicatorOfParameter
    179   elseif ((parCat.eq.128).and.(parNum.eq.77)) then ! W, actually eta dot !added by mc to make it consisitent with new readwind.f90
    180     isec1(6)=135         ! indicatorOfParameter    !added by mc to make it consisitent with new readwind.f90
    181170  elseif ((parCat.eq.3).and.(parNum.eq.0).and.(typSurf.eq.101)) then !SLP
    182171    isec1(6)=151         ! indicatorOfParameter
     
    191180  elseif ((parCat.eq.1).and.(parNum.eq.11).and.(typSurf.eq.1)) then ! SD
    192181    isec1(6)=141         ! indicatorOfParameter
    193     conversion_factor=1000. !added by mc to make it consisitent with new readwind.f90
    194   elseif ((parCat.eq.6).and.(parNum.eq.1) .or. parId .eq. 164) then ! CC !added by mc to make it consisitent with new readwind.f90
     182  elseif ((parCat.eq.6).and.(parNum.eq.1)) then ! CC
    195183    isec1(6)=164         ! indicatorOfParameter
    196   elseif ((parCat.eq.1).and.(parNum.eq.9) .or. parId .eq. 142) then ! LSP !added by mc to make it consisitent with new readwind.f90
     184  elseif ((parCat.eq.1).and.(parNum.eq.9)) then ! LSP
    197185    isec1(6)=142         ! indicatorOfParameter
    198186  elseif ((parCat.eq.1).and.(parNum.eq.10)) then ! CP
    199187    isec1(6)=143         ! indicatorOfParameter
    200     conversion_factor=1000. !added by mc to make it consisitent with new readwind.f90
    201188  elseif ((parCat.eq.0).and.(parNum.eq.11).and.(typSurf.eq.1)) then ! SHF
    202189    isec1(6)=146         ! indicatorOfParameter
    203190  elseif ((parCat.eq.4).and.(parNum.eq.9).and.(typSurf.eq.1)) then ! SR
    204191    isec1(6)=176         ! indicatorOfParameter
    205   elseif ((parCat.eq.2).and.(parNum.eq.17) .or. parId .eq. 180) then ! EWSS !added by mc to make it consisitent with new readwind.f90
     192  elseif ((parCat.eq.2).and.(parNum.eq.17)) then ! EWSS
    206193    isec1(6)=180         ! indicatorOfParameter
    207   elseif ((parCat.eq.2).and.(parNum.eq.18) .or. parId .eq. 181) then ! NSSS !added by mc to make it consisitent with new readwind.f90
     194  elseif ((parCat.eq.2).and.(parNum.eq.18)) then ! NSSS
    208195    isec1(6)=181         ! indicatorOfParameter
    209196  elseif ((parCat.eq.3).and.(parNum.eq.4)) then ! ORO
    210197    isec1(6)=129         ! indicatorOfParameter
    211    elseif ((parCat.eq.3).and.(parNum.eq.7) .or. parId .eq. 160) then ! SDO !added by mc to make it consisitent with new readwind.f90
     198  elseif ((parCat.eq.3).and.(parNum.eq.7)) then ! SDO
    212199    isec1(6)=160         ! indicatorOfParameter
    213200  elseif ((discipl.eq.2).and.(parCat.eq.0).and.(parNum.eq.0).and. &
     
    215202    isec1(6)=172         ! indicatorOfParameter
    216203  else
    217     print*,'***WARNING: undefined GRiB2 message found!',discipl, &
     204    print*,'***ERROR: undefined GRiB2 message found!',discipl, &
    218205         parCat,parNum,typSurf
    219   endif
    220   if(parId .ne. isec1(6) .and. parId .ne. 77) then !added by mc to make it consisitent with new readwind.f90
    221     write(*,*) 'parId',parId, 'isec1(6)',isec1(6)  !
    222 !    stop
    223206  endif
    224207
     
    244227  ! CHECK GRID SPECIFICATIONS
    245228  if(isec2(2).ne.nxn(l)) stop &
    246   'READWIND: NX NOT CONSISTENT FOR A NESTING LEVEL'
     229       'READWIND: NX NOT CONSISTENT FOR A NESTING LEVEL'
    247230  if(isec2(3).ne.nyn(l)) stop &
    248   'READWIND: NY NOT CONSISTENT FOR A NESTING LEVEL'
     231       'READWIND: NY NOT CONSISTENT FOR A NESTING LEVEL'
    249232  if(isec2(12)/2-1.ne.nlev_ec) stop 'READWIND: VERTICAL DISCRET&
    250   IZATION NOT CONSISTENT FOR A NESTING LEVEL'
     233       &IZATION NOT CONSISTENT FOR A NESTING LEVEL'
    251234  endif ! ifield
    252235
    253236  !HSO  get the second part of the grid dimensions only from GRiB1 messages
    254  if (isec1(6) .eq. 167 .and. (gotGrid.eq.0)) then ! !added by mc to make it consisitent with new readwind.f90
     237  if ((gribVer.eq.1).and.(gotGrid.eq.0)) then
    255238    call grib_get_real8(igrib,'longitudeOfFirstGridPointInDegrees', &
    256239         xauxin,iret)
     
    259242         yauxin,iret)
    260243    call grib_check(iret,gribFunction,gribErrorMsg)
    261     if (xauxin.gt.180.) xauxin=xauxin-360.0
    262     if (xauxin.lt.-180.) xauxin=xauxin+360.0
    263 
    264244    xaux=xauxin
    265245    yaux=yauxin
    266     if (abs(xaux-xlon0n(l)).gt.eps) &
    267     stop 'READWIND: LOWER LEFT LONGITUDE NOT CONSISTENT FOR A NESTING LEVEL'
    268     if (abs(yaux-ylat0n(l)).gt.eps) &
    269     stop 'READWIND: LOWER LEFT LATITUDE NOT CONSISTENT FOR A NESTING LEVEL'
     246    xaux0=xlon0n(l)
     247    yaux0=ylat0n(l)
     248    if(xaux.lt.0.) xaux=xaux+360.
     249    if(yaux.lt.0.) yaux=yaux+360.
     250    if(xaux0.lt.0.) xaux0=xaux0+360.
     251    if(yaux0.lt.0.) yaux0=yaux0+360.
     252    if(xaux.ne.xaux0) &
     253         stop 'READWIND: LOWER LEFT LONGITUDE NOT CONSISTENT FOR A NES&
     254         &TING LEVEL'
     255    if(yaux.ne.yaux0) &
     256         stop 'READWIND: LOWER LEFT LATITUDE NOT CONSISTENT FOR A NEST&
     257         &ING LEVEL'
    270258    gotGrid=1
    271259  endif
     
    292280             zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
    293281        if(isec1(6).eq.141) sdn(i,j,1,n,l)= &!! SNOW DEPTH
    294              zsec4(nxn(l)*(nyn(l)-j-1)+i+1)/conversion_factor !added by mc to make it consisitent with new readwind.f90!
     282             zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
    295283        if(isec1(6).eq.151) msln(i,j,1,n,l)= &!! SEA LEVEL PRESS.
    296284             zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
     
    310298        endif
    311299        if(isec1(6).eq.143) then                         !! CONVECTIVE PREC.
    312           convprecn(i,j,1,n,l)=zsec4(nxn(l)*(nyn(l)-j-1)+i+1)/conversion_factor !added by mc to make it consisitent with new readwind.f90
     300          convprecn(i,j,1,n,l)=zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
    313301          if (convprecn(i,j,1,n,l).lt.0.) convprecn(i,j,1,n,l)=0.
    314302        endif
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG