Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/src/readwind.f90

    r24 r20  
    7171  integer :: iret
    7272  integer :: igrib
    73   integer :: gribVer,parCat,parNum,typSurf,valSurf,discipl,parId
     73  integer :: gribVer,parCat,parNum,typSurf,valSurf,discipl
    7474  integer :: gotGrid
    7575  !HSO  end
     
    9090  integer :: isec1(56),isec2(22+nxmax+nymax)
    9191  real(kind=4) :: zsec4(jpunp)
    92   real(kind=4) :: xaux,yaux
     92  real(kind=4) :: xaux,yaux,xaux0,yaux0
    9393  real(kind=8) :: xauxin,yauxin
    9494  real,parameter :: eps=1.e-4
    9595  real(kind=4) :: nsss(0:nxmax-1,0:nymax-1),ewss(0:nxmax-1,0:nymax-1)
    96   real :: plev1,pmean,tv,fu,hlev1,ff10m,fflev1,conversion_factor
     96  real :: plev1,pmean,tv,fu,hlev1,ff10m,fflev1
    9797
    9898  logical :: hflswitch,strswitch
     
    101101  character(len=24) :: gribErrorMsg = 'Error reading grib file'
    102102  character(len=20) :: gribFunction = 'readwind'
     103
     104  !HSO conversion of ECMWF etadot to etadot*dp/deta
     105  logical :: etacon=.false.
     106  real,parameter :: p00=101325.
     107  real :: dak,dbk
    103108
    104109  hflswitch=.false.
     
    150155  endif
    151156
    152   conversion_factor=1.
    153 
    154157  else
    155158
     
    165168  call grib_check(iret,gribFunction,gribErrorMsg)
    166169  call grib_get_int(igrib,'level',valSurf,iret)
    167   call grib_check(iret,gribFunction,gribErrorMsg)
    168   call grib_get_int(igrib,'paramId',parId,iret)
    169170  call grib_check(iret,gribFunction,gribErrorMsg)
    170171
     
    176177  isec1(8)=-1
    177178  isec1(8)=valSurf     ! level
    178   conversion_factor=1.
    179179  if ((parCat.eq.0).and.(parNum.eq.0).and.(typSurf.eq.105)) then ! T
    180180    isec1(6)=130         ! indicatorOfParameter
     
    188188    isec1(6)=134         ! indicatorOfParameter
    189189  elseif ((parCat.eq.2).and.(parNum.eq.32)) then ! W, actually eta dot
    190     isec1(6)=135         ! indicatorOfParameter
    191   elseif ((parCat.eq.128).and.(parNum.eq.77)) then ! W, actually eta dot
    192190    isec1(6)=135         ! indicatorOfParameter
    193191  elseif ((parCat.eq.3).and.(parNum.eq.0).and.(typSurf.eq.101)) then !SLP
     
    203201  elseif ((parCat.eq.1).and.(parNum.eq.11).and.(typSurf.eq.1)) then ! SD
    204202    isec1(6)=141         ! indicatorOfParameter
    205     conversion_factor=1000.
    206   elseif ((parCat.eq.6).and.(parNum.eq.1) .or. parId .eq. 164) then ! CC
     203  elseif ((parCat.eq.6).and.(parNum.eq.1)) then ! CC
    207204    isec1(6)=164         ! indicatorOfParameter
    208   elseif ((parCat.eq.1).and.(parNum.eq.9) .or. parId .eq. 142) then ! LSP
     205  elseif ((parCat.eq.1).and.(parNum.eq.9)) then ! LSP
    209206    isec1(6)=142         ! indicatorOfParameter
    210207  elseif ((parCat.eq.1).and.(parNum.eq.10)) then ! CP
    211208    isec1(6)=143         ! indicatorOfParameter
    212     conversion_factor=1000.
    213209  elseif ((parCat.eq.0).and.(parNum.eq.11).and.(typSurf.eq.1)) then ! SHF
    214210    isec1(6)=146         ! indicatorOfParameter
    215211  elseif ((parCat.eq.4).and.(parNum.eq.9).and.(typSurf.eq.1)) then ! SR
    216212    isec1(6)=176         ! indicatorOfParameter
    217   elseif ((parCat.eq.2).and.(parNum.eq.17) .or. parId .eq. 180) then ! EWSS
     213  elseif ((parCat.eq.2).and.(parNum.eq.17)) then ! EWSS
    218214    isec1(6)=180         ! indicatorOfParameter
    219   elseif ((parCat.eq.2).and.(parNum.eq.18) .or. parId .eq. 181) then ! NSSS
     215  elseif ((parCat.eq.2).and.(parNum.eq.18)) then ! NSSS
    220216    isec1(6)=181         ! indicatorOfParameter
    221217  elseif ((parCat.eq.3).and.(parNum.eq.4)) then ! ORO
    222218    isec1(6)=129         ! indicatorOfParameter
    223   elseif ((parCat.eq.3).and.(parNum.eq.7) .or. parId .eq. 160) then ! SDO
     219  elseif ((parCat.eq.3).and.(parNum.eq.7)) then ! SDO
    224220    isec1(6)=160         ! indicatorOfParameter
    225221  elseif ((discipl.eq.2).and.(parCat.eq.0).and.(parNum.eq.0).and. &
     
    227223    isec1(6)=172         ! indicatorOfParameter
    228224  else
    229     print*,'***WARNING: undefined GRiB2 message found!',discipl, &
     225    print*,'***ERROR: undefined GRiB2 message found!',discipl, &
    230226         parCat,parNum,typSurf
    231   endif
    232   if(parId .ne. isec1(6) .and. parId .ne. 77) then
    233     write(*,*) 'parId',parId, 'isec1(6)',isec1(6)
    234 !    stop
    235227  endif
    236228
     
    245237  !HSO  get the required fields from section 2 in a gribex compatible manner
    246238  if (ifield.eq.1) then
    247   call grib_get_int(igrib,'numberOfPointsAlongAParallel',isec2(2),iret)
    248   call grib_check(iret,gribFunction,gribErrorMsg)
    249   call grib_get_int(igrib,'numberOfPointsAlongAMeridian',isec2(3),iret)
    250   call grib_check(iret,gribFunction,gribErrorMsg)
    251   call grib_get_int(igrib,'numberOfVerticalCoordinateValues',isec2(12))
     239  call grib_get_int(igrib,'numberOfPointsAlongAParallel', &
     240       isec2(2),iret)
     241  call grib_check(iret,gribFunction,gribErrorMsg)
     242  call grib_get_int(igrib,'numberOfPointsAlongAMeridian', &
     243       isec2(3),iret)
     244  call grib_check(iret,gribFunction,gribErrorMsg)
     245  call grib_get_int(igrib,'numberOfVerticalCoordinateValues', &
     246       isec2(12))
    252247  call grib_check(iret,gribFunction,gribErrorMsg)
    253248  ! CHECK GRID SPECIFICATIONS
     
    255250  if(isec2(3).ne.ny) stop 'READWIND: NY NOT CONSISTENT'
    256251  if(isec2(12)/2-1.ne.nlev_ec) &
    257   stop 'READWIND: VERTICAL DISCRETIZATION NOT CONSISTENT'
     252       stop 'READWIND: VERTICAL DISCRETIZATION NOT CONSISTENT'
    258253  endif ! ifield
    259254
    260255  !HSO  get the second part of the grid dimensions only from GRiB1 messages
    261   if (isec1(6) .eq. 167 .and. (gotGrid.eq.0)) then
     256  if ((gribVer.eq.1).and.(gotGrid.eq.0)) then
    262257    call grib_get_real8(igrib,'longitudeOfFirstGridPointInDegrees', &
    263258         xauxin,iret)
     
    266261         yauxin,iret)
    267262    call grib_check(iret,gribFunction,gribErrorMsg)
    268     if (xauxin.gt.180.) xauxin=xauxin-360.0
    269     if (xauxin.lt.-180.) xauxin=xauxin+360.0
    270 
    271263    xaux=xauxin+real(nxshift)*dx
    272264    yaux=yauxin
    273     if (xaux.gt.180.) xaux=xaux-360.0
    274     if(abs(xaux-xlon0).gt.eps) &
    275     stop 'READWIND: LOWER LEFT LONGITUDE NOT CONSISTENT'
    276     if(abs(yaux-ylat0).gt.eps) &
    277     stop 'READWIND: LOWER LEFT LATITUDE NOT CONSISTENT'
     265    xaux0=xlon0
     266    yaux0=ylat0
     267    if(xaux.lt.0.) xaux=xaux+360.
     268    if(yaux.lt.0.) yaux=yaux+360.
     269    if(xaux0.lt.0.) xaux0=xaux0+360.
     270    if(yaux0.lt.0.) yaux0=yaux0+360.
     271    if(abs(xaux-xaux0).gt.eps) &
     272         stop 'READWIND: LOWER LEFT LONGITUDE NOT CONSISTENT'
     273    if(abs(yaux-yaux0).gt.eps) &
     274         stop 'READWIND: LOWER LEFT LATITUDE NOT CONSISTENT'
    278275    gotGrid=1
    279276  endif ! gotGrid
     
    301298           zsec4(nxfield*(ny-j-1)+i+1)
    302299      if(isec1(6).eq.141) sd(i,j,1,n)= &!! SNOW DEPTH
    303            zsec4(nxfield*(ny-j-1)+i+1)/conversion_factor
     300           zsec4(nxfield*(ny-j-1)+i+1)
    304301      if(isec1(6).eq.151) msl(i,j,1,n)= &!! SEA LEVEL PRESS.
    305302           zsec4(nxfield*(ny-j-1)+i+1)
     
    319316      endif
    320317      if(isec1(6).eq.143) then                      !! CONVECTIVE PREC.
    321         convprec(i,j,1,n)=zsec4(nxfield*(ny-j-1)+i+1)/conversion_factor
     318        convprec(i,j,1,n)=zsec4(nxfield*(ny-j-1)+i+1)
    322319        if (convprec(i,j,1,n).lt.0.) convprec(i,j,1,n)=0.
    323320      endif
     
    369366      do j=0,nymin1
    370367        wwh(i,j,nlev_ec+1)=0.
     368      end do
     369    end do
     370  endif
     371
     372  ! convert from ECMWF etadot to etadot*dp/deta as needed by FLEXPART
     373  if(etacon.eqv..true.) then
     374    do k=1,nwzmax
     375      dak=akm(k+1)-akm(k)
     376      dbk=bkm(k+1)-bkm(k)
     377      do i=0,nxmin1
     378        do j=0,nymin1
     379          wwh(i,j,k)=2*wwh(i,j,k)*ps(i,j,1,n)*(dak/ps(i,j,1,n)+dbk)/(dak/p00+dbk)
     380          if (k.gt.1) then
     381            wwh(i,j,k)=wwh(i,j,k)-wwh(i,j,k-1)
     382          endif
     383        end do
    371384      end do
    372385    end do
     
    466479
    467480end subroutine readwind
    468 
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG