Changes in src/gridcheck_gfs.f90 [a756649:467460a] in flexpart.git


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/gridcheck_gfs.f90

    • Property mode changed from 100644 to 100755
    ra756649 r467460a  
    1 !**********************************************************************
    2 ! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
    3 ! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
    4 ! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann   *
    5 !                                                                     *
    6 ! This file is part of FLEXPART.                                      *
    7 !                                                                     *
    8 ! FLEXPART is free software: you can redistribute it and/or modify    *
    9 ! it under the terms of the GNU General Public License as published by*
    10 ! the Free Software Foundation, either version 3 of the License, or   *
    11 ! (at your option) any later version.                                 *
    12 !                                                                     *
    13 ! FLEXPART is distributed in the hope that it will be useful,         *
    14 ! but WITHOUT ANY WARRANTY; without even the implied warranty of      *
    15 ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
    16 ! GNU General Public License for more details.                        *
    17 !                                                                     *
    18 ! You should have received a copy of the GNU General Public License   *
    19 ! along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
    20 !**********************************************************************
     1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
     2! SPDX-License-Identifier: GPL-3.0-or-later
    213
    224subroutine gridcheck_gfs
     
    9375  real :: sizesouth,sizenorth,xauxa,pint
    9476  real :: akm_usort(nwzmax)
    95   real,parameter :: eps=0.0001
     77  real,parameter :: eps=spacing(2.0_4*360.0_4)
    9678
    9779  ! NCEP GFS
    9880  real :: pres(nwzmax), help
    9981
    100   integer :: i179,i180,i181
     82  integer :: i180
    10183
    10284  ! VARIABLES AND ARRAYS NEEDED FOR GRIB DECODING
     
    242224  nxfield=isec2(2)
    243225  ny=isec2(3)
    244   if((abs(xaux1).lt.eps).and.(xaux2.ge.359)) then ! NCEP DATA FROM 0 TO
    245     xaux1=-179.0                             ! 359 DEG EAST ->
    246     xaux2=-179.0+360.-360./real(nxfield)    ! TRANSFORMED TO -179
     226  if((abs(xaux1).lt.eps).and.(xaux2.ge.359.)) then ! NCEP DATA FROM 0 TO
     227    xaux1=-180.0                             ! 359 DEG EAST ->
     228    xaux2=-180.0+360.-360./real(nxfield)    ! TRANSFORMED TO -179
    247229  endif                                      ! TO 180 DEG EAST
    248230  if (xaux1.gt.180) xaux1=xaux1-360.0
     
    323305
    324306
    325   i179=nint(179./dx)
    326   if (dx.lt.0.7) then
    327     i180=nint(180./dx)+1    ! 0.5 deg data
    328   else
    329     i180=nint(179./dx)+1    ! 1 deg data
    330   endif
    331   i181=i180+1
     307  i180=nint(180./dx)    ! 0.5 deg data
    332308
    333309
     
    339315      do ix=0,nxfield-1
    340316        help=zsec4(nxfield*(ny-jy-1)+ix+1)
    341         if(ix.le.i180) then
    342           oro(i179+ix,jy)=help
    343           excessoro(i179+ix,jy)=0.0 ! ISOBARIC SURFACES: SUBGRID TERRAIN DISREGARDED
     317        if(ix.lt.i180) then
     318          oro(i180+ix,jy)=help
     319          excessoro(i180+ix,jy)=0.0 ! ISOBARIC SURFACES: SUBGRID TERRAIN DISREGARDED
    344320        else
    345           oro(ix-i181,jy)=help
    346           excessoro(ix-i181,jy)=0.0 ! ISOBARIC SURFACES: SUBGRID TERRAIN DISREGARDED
     321          oro(ix-i180,jy)=help
     322          excessoro(ix-i180,jy)=0.0 ! ISOBARIC SURFACES: SUBGRID TERRAIN DISREGARDED
    347323        endif
    348324      end do
     
    357333      do ix=0,nxfield-1
    358334        help=zsec4(nxfield*(ny-jy-1)+ix+1)
    359         if(ix.le.i180) then
    360           lsm(i179+ix,jy)=help
     335        if(ix.lt.i180) then
     336          lsm(i180+ix,jy)=help
    361337        else
    362           lsm(ix-i181,jy)=help
     338          lsm(ix-i180,jy)=help
    363339        endif
    364340      end do
     
    431407    write(*,*)
    432408    write(*,*)
    433     write(*,'(a,2i7)') 'Vertical levels in NCEP data: ', &
     409  write(*,'(a,2i7)') '# of vertical levels in NCEP data: ', &
    434410         nuvz,nwz
    435411    write(*,*)
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG