Changes in / [df96ea65:6d73c4b] in flexpart.git


Ignore:
Location:
src
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • src/get_wetscav.f90

    r79e0349 rc7e771d  
    298298          else                                  !parameterize cloudwater m2/m3
    299299!ZHG updated parameterization of cloud water to better reproduce the values coming from ECMWF
    300 ! sec test
    301 !           cl=1E6*1E-7*prec(1)**0.3 !Sec GFS new
    302             cl=1E6*2E-7*prec(1)**0.36 !Sec ECMWF new
    303 !           cl=2E-7*prec(1)**0.36 !Andreas
    304 !           cl=1.6E-6*prec(1)**0.36 !Henrik
     300            cl=1.6E-6*prec(1)**0.36
    305301          endif
    306302
     
    322318          if (dquer(ks).gt.0.) then
    323319            S_i= frac_act/cl
    324 !           write(*,*) 'Si: ',S_i
    325320
    326321! GAS
     
    339334            wetscav=incloud_ratio*S_i*(prec(1)/3.6E6)
    340335          else
    341 !SEC wetscav fix
    342              wetscav=incloud_ratio*S_i*(prec(1)/3.6E6)
    343 !            wetscav=incloud_ratio*S_i*(prec(1)/3.6E6)/clouds_h
     336            wetscav=incloud_ratio*S_i*(prec(1)/3.6E6)/clouds_h
    344337          endif
    345338        endif ! positive in-cloud scavenging parameters given in Species file
  • src/par_mod.f90

    r79e0349 rd944d39  
    148148  ! ECMWF
    149149! integer,parameter :: nxmax=361,nymax=181,nuvzmax=92,nwzmax=92,nzmax=92,nxshift=359 ! 1.0 degree 92 level
    150 !  integer,parameter :: nxmax=361,nymax=181,nuvzmax=138,nwzmax=138,nzmax=138,nxshift=0 ! 1.0 degree 138 level
    151 !   integer,parameter :: nxmax=361,nymax=181,nuvzmax=138,nwzmax=138,nzmax=138,nxshift=359 ! 1.0 degree 138 level
     150 integer,parameter :: nxmax=361,nymax=181,nuvzmax=138,nwzmax=138,nzmax=138,nxshift=0 ! 1.0 degree 138 level
    152151! integer,parameter :: nxmax=721,nymax=361,nuvzmax=138,nwzmax=138,nzmax=138,nxshift=359  ! 0.5 degree 138 level
    153152!  integer,parameter :: nxmax=181,nymax=91,nuvzmax=92,nwzmax=92,nzmax=92,nxshift=0  ! CERA 2.0 degree 92 level
    154153
    155154! GFS
    156    integer,parameter :: nxmax=361,nymax=181,nuvzmax=138,nwzmax=138,nzmax=138
    157    integer :: nxshift=0
     155!  integer,parameter :: nxmax=361,nymax=181,nuvzmax=138,nwzmax=138,nzmax=138,nxshift=0
    158156
    159157
  • src/readwind_gfs.f90

    rdb91eb7 r6ecb30a  
    1 
     1!**********************************************************************
    22! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
    33! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
     
    108108  character(len=24) :: gribErrorMsg = 'Error reading grib file'
    109109  character(len=20) :: gribFunction = 'readwind_gfs'
    110   character(len=20) :: shortname
    111110
    112111
     
    121120
    122121  !HSO
    123   call grib_open_file(ifile,path(3)(1:length(3)) &
     1225   call grib_open_file(ifile,path(3)(1:length(3)) &
    124123         //trim(wfname(indj)),'r',iret)
    125124  if (iret.ne.GRIB_SUCCESS) then
     
    163162
    164163  !read the grib2 identifiers
    165   call grib_get_string(igrib,'shortName',shortname,iret)
    166 
    167164  call grib_get_int(igrib,'discipline',discipl,iret)
    168165!  call grib_check(iret,gribFunction,gribErrorMsg)
     
    176173       valSurf,iret)
    177174!  call grib_check(iret,gribFunction,gribErrorMsg)
    178  
    179 !  write(*,*) 'Field: ',ifield,parCat,parNum,typSurf,shortname
     175
    180176  !convert to grib1 identifiers
    181177  isec1(6)=-1
     
    218214    isec1(7)=105         ! indicatorOfTypeOfLevel
    219215    isec1(8)=10
    220   elseif ((parCat.eq.1).and.(parNum.eq.22).and.(typSurf.eq.100)) then ! CLWMR Cloud Mixing Ratio [kg/kg]:
    221     isec1(6)=153         ! indicatorOfParameter
    222     isec1(7)=100         ! indicatorOfTypeOfLevel
    223     isec1(8)=valSurf/100 ! level, convert to hPa
    224216  elseif ((parCat.eq.3).and.(parNum.eq.1).and.(typSurf.eq.101)) then ! SLP
    225217    isec1(6)=2           ! indicatorOfParameter
     
    556548        endif
    557549      endif
    558 ! SEC & IP 12/2018 read GFS clouds
    559       if(isec1(6).eq.153) then  !! CLWCR  Cloud liquid water content [kg/kg]
    560         clwch(i,j,nlev_ec-k+2,n)=zsec4(nxfield*(ny-j-1)+i+1)
    561         readclouds=.true.
    562         sumclouds=.true.
    563       endif
    564 
    565550
    566551    end do
     
    690675    call shift_field(vvh,nxfield,ny,nuvzmax,nuvz,1,1)
    691676    call shift_field(wwh,nxfield,ny,nwzmax,nwz,1,1)
    692 ! IP & SEC adding GFS Clouds 20181205
    693     call shift_field(clwch,nxfield,ny,nuvzmax,nuvz,2,n)
    694677  endif
    695678
  • src/verttransform_ecmwf.f90

    r79e0349 r47f96e5  
    108108  ! real :: rcw(0:nxmax-1,0:nymax-1)
    109109  ! real :: rpc(0:nxmax-1,0:nymax-1)
    110   character(len=60) :: zhgpath='/xnilu_wrk/users/sec/kleinprojekte/hertlfit/'
    111   character(len=60) :: fnameH,fnameI,fnameJ
     110  ! character(len=60) :: zhgpath='/xnilu_wrk/flex_wrk/zhg/'
    112111  ! character(len=60) :: fnameA,fnameB,fnameC,fnameD,fnameE,fnameF,fnameG,fnameH
    113   CHARACTER(LEN=3)  :: aspec
    114   integer :: virr=0
     112  ! CHARACTER(LEN=3)  :: aspec
     113  ! integer :: virr=0
    115114  !real :: tot_cloud_h
    116115  !real :: dbg_height(nzmax)
     
    733732     !********* TEST ************'**
    734733!teller(:)=0
    735 virr=virr+1
    736 WRITE(aspec, '(i3.3)'), virr
     734!virr=virr+1
     735!WRITE(aspec, '(i3.3)'), virr
    737736
    738737!if (readclouds) then
     
    771770!fnameF=trim(zhgpath)//trim(aspec)//'lsp.txt'
    772771!fnameG=trim(zhgpath)//trim(aspec)//'convp.txt'
    773 if (1.eq.2) then
    774 fnameH=trim(zhgpath)//trim(aspec)//'tcwc.txt'
    775 fnameI=trim(zhgpath)//trim(aspec)//'prec.txt'
    776 fnameJ=trim(zhgpath)//trim(aspec)//'cloudsh.txt'
    777 write(*,*) 'Writing data to file: ',fnameH
    778772!if (readclouds) then
    779773!OPEN(UNIT=111, FILE=fnameA,FORM='FORMATTED',STATUS = 'UNKNOWN')
     
    782776!OPEN(UNIT=114, FILE=fnameD,FORM='FORMATTED',STATUS = 'UNKNOWN')
    783777!else
    784 OPEN(UNIT=115, FILE=fnameH,FORM='FORMATTED',STATUS = 'UNKNOWN')
    785 OPEN(UNIT=116, FILE=fnameI,FORM='FORMATTED',STATUS = 'UNKNOWN')
    786 OPEN(UNIT=117, FILE=fnameJ,FORM='FORMATTED',STATUS = 'UNKNOWN')
     778!OPEN(UNIT=115, FILE=fnameE,FORM='FORMATTED',STATUS = 'UNKNOWN')
     779!OPEN(UNIT=116, FILE=fnameF,FORM='FORMATTED',STATUS = 'UNKNOWN')
     780!OPEN(UNIT=117, FILE=fnameG,FORM='FORMATTED',STATUS = 'UNKNOWN')
    787781!endif
    788782!
    789 do ix=0,nxmin1
     783!do ix=0,nxmin1
    790784!if (readclouds) then
    791785!write(111,*) (icloud_stats(ix,jy,1,n),jy=0,nymin1)
     
    794788!write(114,*) (icloud_stats(ix,jy,4,n),jy=0,nymin1)
    795789!else
    796 write(115,*) (ctwc(ix,jy,n),jy=0,nymin1) 
    797 write(116,*) (lsprec(ix,jy,1,n)+convprec(ix,jy,1,n),jy=0,nymin1)
    798 write(117,*) (cloudsh(ix,jy,n),jy=0,nymin1)
     790!write(115,*) (cloudsh(ix,jy,n),jy=0,nymin1)    !integer
     791!write(116,*) (lsprec(ix,jy,1,n),jy=0,nymin1)   !7.83691406E-02
     792!write(117,*) (convprec(ix,jy,1,n),jy=0,nymin1) !5.38330078E-02
    799793!endif
    800 end do
     794!end do
    801795!
    802796!if (readclouds) then
     
    806800!CLOSE(114)
    807801!else
    808 CLOSE(115)
    809 CLOSE(116)
    810 CLOSE(117)
    811 endif
     802!CLOSE(115)
     803!CLOSE(116)
     804!CLOSE(117)
    812805!endif
    813806!
  • 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