Changeset 467460a in flexpart.git for src/gridcheck_gfs.f90


Ignore:
Timestamp:
Mar 13, 2021, 10:00:37 AM (3 years ago)
Author:
Espen Sollum ATMOS <eso@…>
Branches:
GFS_025, dev
Children:
9ca6e38
Parents:
759df5f
Message:

First commit of files from Hachinger

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/gridcheck_gfs.f90

    • Property mode changed from 100644 to 100755
    ra803521 r467460a  
    7575  real :: sizesouth,sizenorth,xauxa,pint
    7676  real :: akm_usort(nwzmax)
    77   real,parameter :: eps=0.0001
     77  real,parameter :: eps=spacing(2.0_4*360.0_4)
    7878
    7979  ! NCEP GFS
    8080  real :: pres(nwzmax), help
    8181
    82   integer :: i179,i180,i181
     82  integer :: i180
    8383
    8484  ! VARIABLES AND ARRAYS NEEDED FOR GRIB DECODING
     
    224224  nxfield=isec2(2)
    225225  ny=isec2(3)
    226   if((abs(xaux1).lt.eps).and.(xaux2.ge.359)) then ! NCEP DATA FROM 0 TO
    227     xaux1=-179.0                             ! 359 DEG EAST ->
    228     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
    229229  endif                                      ! TO 180 DEG EAST
    230230  if (xaux1.gt.180) xaux1=xaux1-360.0
     
    305305
    306306
    307   i179=nint(179./dx)
    308   if (dx.lt.0.7) then
    309     i180=nint(180./dx)+1    ! 0.5 deg data
    310   else
    311     i180=nint(179./dx)+1    ! 1 deg data
    312   endif
    313   i181=i180+1
     307  i180=nint(180./dx)    ! 0.5 deg data
    314308
    315309
     
    321315      do ix=0,nxfield-1
    322316        help=zsec4(nxfield*(ny-jy-1)+ix+1)
    323         if(ix.le.i180) then
    324           oro(i179+ix,jy)=help
    325           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
    326320        else
    327           oro(ix-i181,jy)=help
    328           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
    329323        endif
    330324      end do
     
    339333      do ix=0,nxfield-1
    340334        help=zsec4(nxfield*(ny-jy-1)+ix+1)
    341         if(ix.le.i180) then
    342           lsm(i179+ix,jy)=help
     335        if(ix.lt.i180) then
     336          lsm(i180+ix,jy)=help
    343337        else
    344           lsm(ix-i181,jy)=help
     338          lsm(ix-i180,jy)=help
    345339        endif
    346340      end do
     
    413407    write(*,*)
    414408    write(*,*)
    415     write(*,'(a,2i7)') 'Vertical levels in NCEP data: ', &
     409  write(*,'(a,2i7)') '# of vertical levels in NCEP data: ', &
    416410         nuvz,nwz
    417411    write(*,*)
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG