Changes in src/verttransform_gfs.f90 [db91eb7:6ecb30a] in flexpart.git


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/verttransform_gfs.f90

    rdb91eb7 r6ecb30a  
    7575  integer :: rain_cloud_above,kz_inv
    7676  real :: f_qvsat,pressure
    77   real :: rh,lsp,cloudh_min,convp,prec
     77  real :: rh,lsp,convp
    7878  real :: rhoh(nuvzmax),pinmconv(nzmax)
    7979  real :: ew,pint,tv,tvold,pold,dz1,dz2,dz,ui,vi
     
    224224      tt(ix,jy,1,n)=tth(ix,jy,llev,n)
    225225      qv(ix,jy,1,n)=qvh(ix,jy,llev,n)
    226 ! IP & SEC, 201812 add clouds
    227       if (readclouds) then
    228          clwc(ix,jy,1,n)=clwch(ix,jy,llev,n)
    229       endif
    230226      pv(ix,jy,1,n)=pvh(ix,jy,llev)
    231227      rho(ix,jy,1,n)=rhoh(llev)
     
    235231      tt(ix,jy,nz,n)=tth(ix,jy,nuvz,n)
    236232      qv(ix,jy,nz,n)=qvh(ix,jy,nuvz,n)
    237 ! IP & SEC, 201812 add clouds
    238       if (readclouds) then
    239          clwc(ix,jy,nz,n)=clwch(ix,jy,nuvz,n)
    240       endif
    241233      pv(ix,jy,nz,n)=pvh(ix,jy,nuvz)
    242234      rho(ix,jy,nz,n)=rhoh(nuvz)
     
    250242            tt(ix,jy,iz,n)=tt(ix,jy,nz,n)
    251243            qv(ix,jy,iz,n)=qv(ix,jy,nz,n)
    252 ! IP & SEC, 201812 add clouds
    253             if (readclouds) then
    254                clwc(ix,jy,iz,n)=clwc(ix,jy,nz,n)
    255             endif
    256244            pv(ix,jy,iz,n)=pv(ix,jy,nz,n)
    257245            rho(ix,jy,iz,n)=rho(ix,jy,nz,n)
     
    270258            qv(ix,jy,iz,n)=(qvh(ix,jy,kz-1,n)*dz2 &
    271259            +qvh(ix,jy,kz,n)*dz1)/dz
    272 ! IP & SEC, 201812 add clouds
    273             if (readclouds) then
    274                clwc(ix,jy,iz,n)=(clwch(ix,jy,kz-1,n)*dz2 &
    275                +clwch(ix,jy,kz,n)*dz1)/dz
    276             endif
    277260            pv(ix,jy,iz,n)=(pvh(ix,jy,kz-1)*dz2+pvh(ix,jy,kz)*dz1)/dz
    278261            rho(ix,jy,iz,n)=(rhoh(kz-1)*dz2+rhoh(kz)*dz1)/dz
     
    513496
    514497
    515 
    516 !***********************************************************************************
    517 ! IP & SEC, 201812 GFS clouds read
    518   if (readclouds) then
    519 ! The method is loops all grids vertically and constructs the 3D matrix for clouds
    520 ! Cloud top and cloud bottom gid cells are assigned as well as the total column
    521 ! cloud water. For precipitating grids, the type and whether it is in or below
    522 ! cloud scavenging are assigned with numbers 2-5 (following the old metod).
    523 ! Distinction is done for lsp and convp though they are treated the same in regards
    524 ! to scavenging. Also clouds that are not precipitating are defined which may be
    525 ! to include future cloud processing by non-precipitating-clouds.
    526 !***********************************************************************************
    527     write(*,*) 'Global NCEP fields: using cloud water'
    528     clw(:,:,:,n)=0.0
    529     ctwc(:,:,n)=0.0
    530     clouds(:,:,:,n)=0
    531 ! If water/ice are read separately into clwc and ciwc, store sum in clwc
    532     do jy=0,nymin1
    533       do ix=0,nxmin1
    534         lsp=lsprec(ix,jy,1,n)
    535         convp=convprec(ix,jy,1,n)
    536         prec=lsp+convp
    537 ! Find clouds in the vertical
    538         do kz=1, nz-1 !go from top to bottom
    539           if (clwc(ix,jy,kz,n).gt.0) then
    540 ! assuming rho is in kg/m3 and hz in m gives: kg/kg * kg/m3 *m3/kg /m = m2/m3
    541             clw(ix,jy,kz,n)=(clwc(ix,jy,kz,n)*rho(ix,jy,kz,n))*(height(kz+1)-height(kz))
    542             ctwc(ix,jy,n) = ctwc(ix,jy,n)+clw(ix,jy,kz,n)
    543             cloudh_min=min(height(kz+1),height(kz))
    544           endif
    545         end do
    546 
    547 ! If Precipitation. Define removal type in the vertical
    548         if ((lsp.gt.0.01).or.(convp.gt.0.01)) then ! cloud and precipitation
    549 
    550           do kz=nz,1,-1 !go Bottom up!
    551             if (clw(ix,jy,kz,n).gt. 0) then ! is in cloud
    552               cloudsh(ix,jy,n)=cloudsh(ix,jy,n)+height(kz)-height(kz-1)
    553               clouds(ix,jy,kz,n)=1                               ! is a cloud
    554               if (lsp.ge.convp) then
    555                 clouds(ix,jy,kz,n)=3                            ! lsp in-cloud
    556               else
    557                 clouds(ix,jy,kz,n)=2                             ! convp in-cloud
    558               endif                                              ! convective or large scale
    559             elseif((clw(ix,jy,kz,n).le.0) .and. (cloudh_min.ge.height(kz))) then ! is below cloud
    560               if (lsp.ge.convp) then
    561                 clouds(ix,jy,kz,n)=5                             ! lsp dominated washout
    562               else
    563                 clouds(ix,jy,kz,n)=4                             ! convp dominated washout
    564               endif                                              ! convective or large scale
    565             endif
    566 
    567             if (height(kz).ge. 19000) then                        ! set a max height for removal
    568               clouds(ix,jy,kz,n)=0
    569             endif !clw>0
    570           end do !nz
    571         endif ! precipitation
    572       end do
    573     end do
    574   else
    575   write(*,*) 'Global NCEP fields: using cloud water from Parameterization'
    576498  !   write (*,*) 'initializing clouds, n:',n,nymin1,nxmin1,nz
    577499  !   create a cloud and rainout/washout field, clouds occur where rh>80%
     
    612534    end do
    613535  end do
    614   endif  ! IP & SEC 201812, GFS clouds read
    615536
    616537
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG