Changeset 0a94e13 in flexpart.git for src/com_mod.f90


Ignore:
Timestamp:
May 6, 2019, 11:43:21 AM (5 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
Children:
0c8c7f2
Parents:
328fdf9
Message:

Added ipout=3 option for time averaged particle output

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/com_mod.f90

    r328fdf9 r0a94e13  
    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)
     
    128131
    129132  logical :: gdomainfill
    130 
    131133  ! gdomainfill             .T., if domain-filling is global, .F. if not
    132134
     
    675677  real, allocatable, dimension(:,:) :: xscav_frac1
    676678
     679! Variables used for writing out interval averages for partoutput
     680!****************************************************************
     681
     682  integer, allocatable, dimension(:) :: npart_av
     683  real, allocatable, dimension(:) :: part_av_cartx,part_av_carty,part_av_cartz,part_av_z,part_av_topo
     684  real, allocatable, dimension(:) :: part_av_pv,part_av_qv,part_av_tt,part_av_rho,part_av_tro,part_av_hmix
     685  real, allocatable, dimension(:) :: part_av_uu,part_av_vv,part_av_energy
     686
    677687  ! eso: Moved from timemanager
    678688  real, allocatable, dimension(:) :: uap,ucp,uzp,us,vs,ws
     
    781791         & idt(nmpart),itramem(nmpart),itrasplit(nmpart),&
    782792         & xtra1(nmpart),ytra1(nmpart),ztra1(nmpart),&
    783          & xmass1(nmpart, maxspec),&
    784          & checklifetime(nmpart,maxspec), species_lifetime(maxspec,2))!CGZ-lifetime
     793         & xmass1(nmpart, maxspec))  ! ,&
     794!         & checklifetime(nmpart,maxspec), species_lifetime(maxspec,2))!CGZ-lifetime
     795
     796    if (ipout.eq.3) then
     797      allocate(npart_av(nmpart),part_av_cartx(nmpart),part_av_carty(nmpart),&
     798           & part_av_cartz(nmpart),part_av_z(nmpart),part_av_topo(nmpart))
     799      allocate(part_av_pv(nmpart),part_av_qv(nmpart),part_av_tt(nmpart),&
     800           & part_av_rho(nmpart),part_av_tro(nmpart),part_av_hmix(nmpart))
     801      allocate(part_av_uu(nmpart),part_av_vv(nmpart),part_av_energy(nmpart))
     802    end if
    785803
    786804
    787805    allocate(uap(nmpart),ucp(nmpart),uzp(nmpart),us(nmpart),&
    788806         & vs(nmpart),ws(nmpart),cbt(nmpart))
    789    
     807
    790808  end subroutine com_mod_allocate_part
    791809
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG