Changeset 6ecb30a in flexpart.git for src/convmix.f90


Ignore:
Timestamp:
Aug 17, 2017, 4:39:17 PM (7 years ago)
Author:
Espen Sollum ATMOS <eso@…>
Branches:
master, 10.4.1_pesei, GFS_025, bugfixes+enhancements, dev, release-10, release-10.4.1, scaling-bug, univie
Children:
5b34509
Parents:
61e07ba
Message:

Merged changes from CTBTO project

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/convmix.f90

    r8a65cb0 r6ecb30a  
    2020!**********************************************************************
    2121
    22 subroutine convmix(itime)
     22subroutine convmix(itime,metdata_format)
    2323  !                     i
    2424  !**************************************************************
     
    3131  !CHANGES by A. Stohl:
    3232  !  various run-time optimizations - February 2005
     33  ! CHANGES by C. Forster, November 2005, NCEP GFS version
     34  !      in the ECMWF version convection is calculated on the
     35  !      original eta-levels
     36  !      in the GFS version convection is calculated on the
     37  !      FLEXPART levels
     38  !
     39  !   Unified ECMWF and GFS builds                                             
     40  !   Marian Harustak, 12.5.2017                                             
     41  !     - Merged convmix and convmix_gfs into one routine using if-then           
     42  !       for meteo-type dependent code                                       
    3343  !**************************************************************
    3444
     
    3747  use com_mod
    3848  use conv_mod
     49  use class_gribfile
    3950
    4051  implicit none
     
    4455  integer :: jy, kpart, ktop, ngrid,kz
    4556  integer :: igrid(maxpart), ipoint(maxpart), igridn(maxpart,maxnests)
     57  integer :: metdata_format
    4658
    4759  ! itime [s]                 current time
     
    104116
    105117    ngrid=0
     118    if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    106119    do j=numbnests,1,-1
    107120      if ( x.gt.xln(j)+eps .and. x.lt.xrn(j)-eps .and. &
     
    111124      endif
    112125    end do
     126    else
     127      do j=numbnests,1,-1
     128        if ( x.gt.xln(j) .and. x.lt.xrn(j) .and. &
     129             y.gt.yln(j) .and. y.lt.yrn(j) ) then
     130          ngrid=j
     131          goto 23
     132        endif
     133      end do
     134    endif
    113135 23   continue
    114136
     
    167189      td2conv=(td2(ix,jy,1,mind1)*dt2+td2(ix,jy,1,mind2)*dt1)*dtt
    168190!!$      do kz=1,nconvlev+1      !old
     191      if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    169192        do kz=1,nuvz-1           !bugfix
    170193        tconv(kz)=(tth(ix,jy,kz+1,mind1)*dt2+ &
     
    173196             qvh(ix,jy,kz+1,mind2)*dt1)*dtt
    174197      end do
     198      else
     199        do kz=1,nuvz-1           !bugfix
     200          pconv(kz)=(pplev(ix,jy,kz,mind1)*dt2+ &
     201              pplev(ix,jy,kz,mind2)*dt1)*dtt
     202          tconv(kz)=(tt(ix,jy,kz,mind1)*dt2+ &
     203              tt(ix,jy,kz,mind2)*dt1)*dtt
     204          qconv(kz)=(qv(ix,jy,kz,mind1)*dt2+ &
     205              qv(ix,jy,kz,mind2)*dt1)*dtt
     206        end do
     207      end if
    175208
    176209  ! Calculate translocation matrix
    177       call calcmatrix(lconv,delt,cbaseflux(ix,jy))
     210      call calcmatrix(lconv,delt,cbaseflux(ix,jy),metdata_format)
    178211      igrold = igr
    179212      ktop = 0
     
    252285  ! calculate translocation matrix
    253286  !*******************************
    254         call calcmatrix(lconv,delt,cbasefluxn(ix,jy,inest))
     287        call calcmatrix(lconv,delt,cbasefluxn(ix,jy,inest),metdata_format)
    255288        igrold = igr
    256289        ktop = 0
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG