Changes in src/com_mod.f90 [e9e0f06:2eefa58] in flexpart.git


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/com_mod.f90

    re9e0f06 r2eefa58  
    1818
    1919  implicit none
     20
     21
    2022
    2123  !****************************************************************
     
    6971
    7072  real :: ctl,fine
    71   integer :: ifine,iout,ipout,ipin,iflux,mdomainfill
     73  integer :: ifine,iout,ipout,ipin,iflux,mdomainfill,ipoutfac
    7274  integer :: mquasilag,nested_output,ind_source,ind_receptor
    7375  integer :: ind_rel,ind_samp,ioutputforeachrelease,linit_cond,surf_only
     
    8284  ! iout     output options: 1 conc. output (ng/m3), 2 mixing ratio (pptv), 3 both
    8385  ! ipout    particle dump options: 0 no, 1 every output interval, 2 only at end
     86  ! ipoutfac increase particle dump interval by factor (default 1)
    8487  ! ipin     read in particle positions from dumped file from a previous run
    8588  ! fine     real(ifine)
     
    121124  ! lnetcdfout   1 for netcdf grid output, 0 if not. Set in COMMAND (namelist input)
    122125
     126  integer :: linversionout
     127  ! linversionout 1 for one grid_time output file for each release containing all timesteps
     128
    123129  integer :: nageclass,lage(maxageclass)
    124130
     
    128134
    129135  logical :: gdomainfill
    130 
    131136  ! gdomainfill             .T., if domain-filling is global, .F. if not
    132137
     
    174179  real :: ri(5,numclass),rac(5,numclass),rcl(maxspec,5,numclass)
    175180  real :: rgs(maxspec,5,numclass),rlu(maxspec,5,numclass)
    176   real :: rm(maxspec),dryvel(maxspec)
     181  real :: rm(maxspec),dryvel(maxspec),kao(maxspec)
    177182  real :: ohcconst(maxspec),ohdconst(maxspec),ohnconst(maxspec)
    178183
     
    359364  real :: ciwc(0:nxmax-1,0:nymax-1,nzmax,numwfmem)=0.0 !ice      [kg/kg]
    360365  real :: clw(0:nxmax-1,0:nymax-1,nzmax,numwfmem)=0.0  !combined [m3/m3]
    361 
     366! RLT add pressure and dry air density
     367  real :: prs(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
     368  real :: rho_dry(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
    362369  real :: pv(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
    363370  real :: rho(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
     
    381388  ! uupol,vvpol [m/s]    wind components in polar stereographic projection
    382389  ! tt [K]               temperature data
     390  ! prs                  air pressure
    383391  ! qv                   specific humidity data
    384392  ! pv (pvu)             potential vorticity
     
    651659  real :: receptorarea(maxreceptor)
    652660  real :: creceptor(maxreceptor,maxspec)
     661  real, allocatable, dimension(:,:) :: creceptor0
    653662  character(len=16) :: receptorname(maxreceptor)
    654663  integer :: numreceptor
     
    673682  real, allocatable, dimension(:,:) :: xmass1
    674683  real, allocatable, dimension(:,:) :: xscav_frac1
     684
     685! Variables used for writing out interval averages for partoutput
     686!****************************************************************
     687
     688  integer, allocatable, dimension(:) :: npart_av
     689  real, allocatable, dimension(:) :: part_av_cartx,part_av_carty,part_av_cartz,part_av_z,part_av_topo
     690  real, allocatable, dimension(:) :: part_av_pv,part_av_qv,part_av_tt,part_av_rho,part_av_tro,part_av_hmix
     691  real, allocatable, dimension(:) :: part_av_uu,part_av_vv,part_av_energy
    675692
    676693  ! eso: Moved from timemanager
     
    780797         & idt(nmpart),itramem(nmpart),itrasplit(nmpart),&
    781798         & xtra1(nmpart),ytra1(nmpart),ztra1(nmpart),&
    782          & xmass1(nmpart, maxspec),&
    783          & checklifetime(nmpart,maxspec), species_lifetime(maxspec,2))!CGZ-lifetime
     799         & xmass1(nmpart, maxspec))  ! ,&
     800!         & checklifetime(nmpart,maxspec), species_lifetime(maxspec,2))!CGZ-lifetime
     801
     802    if (ipout.eq.3) then
     803      allocate(npart_av(nmpart),part_av_cartx(nmpart),part_av_carty(nmpart),&
     804           & part_av_cartz(nmpart),part_av_z(nmpart),part_av_topo(nmpart))
     805      allocate(part_av_pv(nmpart),part_av_qv(nmpart),part_av_tt(nmpart),&
     806           & part_av_rho(nmpart),part_av_tro(nmpart),part_av_hmix(nmpart))
     807      allocate(part_av_uu(nmpart),part_av_vv(nmpart),part_av_energy(nmpart))
     808    end if
    784809
    785810
    786811    allocate(uap(nmpart),ucp(nmpart),uzp(nmpart),us(nmpart),&
    787812         & vs(nmpart),ws(nmpart),cbt(nmpart))
    788    
     813
    789814  end subroutine com_mod_allocate_part
    790815
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG