Changeset d6a0977 in flexpart.git for src/verttransform.f90


Ignore:
Timestamp:
Dec 14, 2015, 3:10:04 PM (8 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:
f75967d
Parents:
88d8c3d
Message:

Updates to Henrik's wet depo scheme

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/verttransform.f90

    r4d45639 rd6a0977  
    9797  logical :: init = .true.
    9898
    99 !hg
     99  !ZHG SEP 2014 tests
    100100  integer :: cloud_ver,cloud_min, cloud_max
     101  integer ::teller(5), convpteller=0, lspteller=0
    101102  real :: cloud_col_wat, cloud_water
    102 !hg temporary variables for testing
     103  !ZHG 2015 temporary variables for testing
    103104  real :: rcw(0:nxmax-1,0:nymax-1)
    104105  real :: rpc(0:nxmax-1,0:nymax-1)
    105 !hg
     106  character(len=60) :: zhgpath='/xnilu_wrk/flex_wrk/zhg/'
     107  character(len=60) :: fnameA,fnameB,fnameC,fnameD,fnameE,fnameF,fnameG,fnameH
     108  CHARACTER(LEN=3)  :: aspec
     109  integer :: virr=0
     110  real :: tot_cloud_h
     111!ZHG
    106112
    107113!*************************************************************************
     
    561567
    562568
     569!*********************************************************************************** 
     570if (readclouds) then !HG METHOD
     571! The method is loops all grids vertically and constructs the 3D matrix for clouds
     572! Cloud top and cloud bottom gid cells are assigned as well as the total column
     573! cloud water. For precipitating grids, the type and whether it is in or below
     574! cloud scavenging are assigned with numbers 2-5 (following the old metod).
     575! Distinction is done for lsp and convp though they are treated the same in regards
     576! to scavenging. Also clouds that are not precipitating are defined which may be
     577! to include future cloud processing by non-precipitating-clouds.
     578!***********************************************************************************
    563579  if (readclouds) write(*,*) 'using cloud water from ECMWF'
    564 !  if (.not.readclouds) write(*,*) 'using cloud water from parameterization'
    565 
    566   rcw(:,:)=0
    567   rpc(:,:)=0
    568 
     580  clw(:,:,:,n)=0
     581  icloud_stats(:,:,:,n)=0
     582  clouds(:,:,:,n)=0
     583  do jy=0,nymin1
     584   do ix=0,nxmin1
     585    lsp=lsprec(ix,jy,1,n)
     586    convp=convprec(ix,jy,1,n)
     587    prec=lsp+convp
     588    tot_cloud_h=0
     589    ! Find clouds in the vertical
     590    do kz=1, nz-1 !go from top to bottom
     591     if (clwc(ix,jy,kz,n).gt.0) then     
     592      ! assuming rho is in kg/m3 and hz in m gives: kg/kg * kg/m3 *m3/kg /m = m2/m3
     593      clw(ix,jy,kz,n)=(clwc(ix,jy,kz,n)*rho(ix,jy,kz,n))*(height(kz+1)-height(kz))
     594      tot_cloud_h=tot_cloud_h+(height(kz+1)-height(kz))
     595      icloud_stats(ix,jy,4,n)= icloud_stats(ix,jy,4,n)+clw(ix,jy,kz,n)          ! Column cloud water [m3/m3]
     596      icloud_stats(ix,jy,3,n)= min(height(kz+1),height(kz))                     ! Cloud BOT height stats      [m]
     597!ZHG 2015 extra for testing
     598      clh(ix,jy,kz,n)=height(kz+1)-height(kz)
     599      icloud_stats(ix,jy,1,n)=icloud_stats(ix,jy,1,n)+(height(kz+1)-height(kz)) ! Cloud total vertical extent [m]
     600      icloud_stats(ix,jy,2,n)= max(icloud_stats(ix,jy,2,n),height(kz))          ! Cloud TOP height            [m]
     601!ZHG
     602    endif
     603    end do
     604
     605   ! If Precipitation. Define removal type in the vertical
     606  if ((lsp.gt.0.01).or.(convp.gt.0.01)) then ! cloud and precipitation
     607
     608    do kz=nz,1,-1 !go Bottom up!
     609     if (clw(ix,jy,kz,n).gt. 0) then ! is in cloud
     610        cloudsh(ix,jy,n)=cloudsh(ix,jy,n)+height(kz)-height(kz-1)
     611        clouds(ix,jy,kz,n)=1                               ! is a cloud
     612        if (lsp.ge.convp) then
     613           clouds(ix,jy,kz,n)=3                            ! lsp in-cloud
     614        else
     615          clouds(ix,jy,kz,n)=2                             ! convp in-cloud
     616        endif                                              ! convective or large scale
     617     elseif((clw(ix,jy,kz,n).le.0) .and. (icloud_stats(ix,jy,3,n).ge.height(kz)) ) then ! is below cloud
     618        if (lsp.ge.convp) then
     619          clouds(ix,jy,kz,n)=5                             ! lsp dominated washout
     620        else
     621          clouds(ix,jy,kz,n)=4                             ! convp dominated washout
     622        endif                                              ! convective or large scale
     623     endif
     624
     625     if (height(kz).ge. 19000) then                        ! set a max height for removal
     626        clouds(ix,jy,kz,n)=0
     627     endif !clw>0
     628    end do !nz
     629   endif ! precipitation
     630  end do
     631 end do
     632!**************************************************************************
     633 else       ! use old definitions
     634!**************************************************************************
     635!   create a cloud and rainout/washout field, clouds occur where rh>80%
     636!   total cloudheight is stored at level 0
     637 if (.not.readclouds) write(*,*) 'using cloud water from Parameterization'
    569638  do jy=0,nymin1
    570639    do ix=0,nxmin1
     
    603672      end do
    604673!END OLD METHOD
     674      end do
     675     end do
     676endif !readclouds
     677
     678     !********* TEST ***************
     679     ! WRITE OUT SOME TEST VARIABLES
     680     !********* TEST ************'**
     681!teller(:)=0
     682!virr=virr+1
     683!WRITE(aspec, '(i3.3)'), virr
     684
     685!if (readclouds) then
     686!fnameH=trim(zhgpath)//trim(aspec)//'Vertical_placement.txt'
     687!else
     688!fnameH=trim(zhgpath)//trim(aspec)//'Vertical_placement_old.txt'
     689!endif
     690!
     691!OPEN(UNIT=118, FILE=fnameH,FORM='FORMATTED',STATUS = 'UNKNOWN')
     692!do kz_inv=1,nz-1
     693!  kz=nz-kz_inv+1
     694!  !kz=91
     695!  do jy=0,nymin1
     696!     do ix=0,nxmin1
     697!          if (clouds(ix,jy,kz,n).eq.1) teller(1)=teller(1)+1 ! no precipitation cloud
     698!          if (clouds(ix,jy,kz,n).eq.2) teller(2)=teller(2)+1 ! convp dominated rainout
     699!          if (clouds(ix,jy,kz,n).eq.3) teller(3)=teller(3)+1 ! lsp dominated rainout
     700!          if (clouds(ix,jy,kz,n).eq.4) teller(4)=teller(4)+1 ! convp dominated washout
     701!          if (clouds(ix,jy,kz,n).eq.5) teller(5)=teller(5)+1 ! lsp dominated washout
     702!         
     703!        !  write(*,*) height(kz),teller
     704!     end do
     705!  end do
     706!  write(118,*) height(kz),teller
     707!  teller(:)=0
     708!end do
     709!teller(:)=0
     710!write(*,*) teller
     711!write(*,*) aspec
     712!
     713!fnameA=trim(zhgpath)//trim(aspec)//'cloudV.txt'
     714!fnameB=trim(zhgpath)//trim(aspec)//'cloudT.txt'
     715!fnameC=trim(zhgpath)//trim(aspec)//'cloudB.txt'
     716!fnameD=trim(zhgpath)//trim(aspec)//'cloudW.txt'
     717!fnameE=trim(zhgpath)//trim(aspec)//'old_cloudV.txt'
     718!fnameF=trim(zhgpath)//trim(aspec)//'lsp.txt'
     719!fnameG=trim(zhgpath)//trim(aspec)//'convp.txt'
     720!if (readclouds) then
     721!OPEN(UNIT=111, FILE=fnameA,FORM='FORMATTED',STATUS = 'UNKNOWN')
     722!OPEN(UNIT=112, FILE=fnameB,FORM='FORMATTED',STATUS = 'UNKNOWN')
     723!OPEN(UNIT=113, FILE=fnameC,FORM='FORMATTED',STATUS = 'UNKNOWN')
     724!OPEN(UNIT=114, FILE=fnameD,FORM='FORMATTED',STATUS = 'UNKNOWN')
     725!else
     726!OPEN(UNIT=115, FILE=fnameE,FORM='FORMATTED',STATUS = 'UNKNOWN')
     727!OPEN(UNIT=116, FILE=fnameF,FORM='FORMATTED',STATUS = 'UNKNOWN')
     728!OPEN(UNIT=117, FILE=fnameG,FORM='FORMATTED',STATUS = 'UNKNOWN')
     729!endif
     730!
     731!do ix=0,nxmin1
     732!if (readclouds) then
     733!write(111,*) (icloud_stats(ix,jy,1,n),jy=0,nymin1)
     734!write(112,*) (icloud_stats(ix,jy,2,n),jy=0,nymin1)
     735!write(113,*) (icloud_stats(ix,jy,3,n),jy=0,nymin1)
     736!write(114,*) (icloud_stats(ix,jy,4,n),jy=0,nymin1)
     737!else
     738!write(115,*) (cloudsh(ix,jy,n),jy=0,nymin1)    !integer
     739!write(116,*) (lsprec(ix,jy,1,n),jy=0,nymin1)   !7.83691406E-02
     740!write(117,*) (convprec(ix,jy,1,n),jy=0,nymin1) !5.38330078E-02
     741!endif
     742!end do
     743!
     744!if (readclouds) then
     745!CLOSE(111)
     746!CLOSE(112)
     747!CLOSE(113)
     748!CLOSE(114)
     749!else
     750!CLOSE(115)
     751!CLOSE(116)
     752!CLOSE(117)
     753!endif
     754!
     755!END ********* TEST *************** END
     756! WRITE OUT SOME TEST VARIABLES
     757!END ********* TEST *************** END
     758
    605759
    606760! PS 2012
     
    613767!            lconvectprec = .true.
    614768!           endif
    615 !HG METHOD
    616 !readclouds =.true.
    617 !      if (readclouds) then
    618 !hg added APR 2014  Cloud Water=clwc(ix,jy,kz,n)  Cloud Ice=ciwc(ix,jy,kz,n)
    619 !hg Use the cloud water variables to determine existence of clouds. This makes the PS code obsolete
    620 !        cloud_min=99999
    621 !        cloud_max=-1
    622 !        cloud_col_wat=0
    623 
    624 !        do kz=1, nz
    625 !         !clw & ciw are given in kg/kg 
    626           ! cloud_water=clwc(ix,jy,kz,n)+ciwc(ix,jy,kz,n)
    627           ! if (cloud_water .gt. 0) then
    628           !   cloud_min=min(nint(height(kz)),cloud_min) !hg needs reset each grid
    629           !   cloud_max=max(nint(height(kz)),cloud_max) !hg needs reset each grid
    630           !   cloud_col_wat=cloud_col_wat+cloud_water !hg needs reset each grid
    631           ! endif
    632           ! cloud_ver=max(0,cloud_max-cloud_min)
    633 
    634           ! icloudbot(ix,jy,n)=cloud_min
    635           ! icloudthck(ix,jy,n)=cloud_ver
    636           ! rcw(ix,jy)=cloud_col_wat
    637           ! rpc(ix,jy)=prec
    638 !write(*,*) 'Using clouds from ECMWF' !hg END Henrik Code
    639 !END HG METHOD
    640 
    641 
    642 
    643769!      else ! windfields does not contain cloud data
    644770!          rhmin = 0.90 ! standard condition for presence of clouds
     
    698824!      endif !hg read clouds
    699825
    700     end do
    701   end do
    702 
    703 !do 102 kz=1,nuvz
    704 !write(an,'(i02)') kz+10
    705 !write(*,*) nuvz,nymin1,nxmin1,'--',an,'--'
    706 !open(4,file='/nilu_wrk2/sec/cloudtest/cloud'//an,form='formatted')
    707 !do 101 jy=0,nymin1
    708 !    write(4,*) (clouds(ix,jy,kz,n),ix=1,nxmin1)
    709 !101   continue
    710 ! close(4)
    711 !102   continue
    712 
    713 ! open(4,file='/nilu_wrk2/sec/cloudtest/height',form='formatted')
    714 ! do 103 jy=0,nymin1
    715 !     write (4,*)
    716 !+       (height(kz),kz=1,nuvz)
    717 !103   continue
    718 ! close(4)
    719 
    720 !open(4,file='/nilu_wrk2/sec/cloudtest/p',form='formatted')
    721 ! do 104 jy=0,nymin1
    722 !     write (4,*)
    723 !+       (r_air*tt(ix,jy,1,n)*rho(ix,jy,1,n),ix=1,nxmin1)
    724 !104   continue
    725 ! close(4)
     826
     827
    726828
    727829!eso measure CPU time
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG