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


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/com_mod.f90

    r2eefa58 re9e0f06  
    1818
    1919  implicit none
    20 
    21 
    2220
    2321  !****************************************************************
     
    7169
    7270  real :: ctl,fine
    73   integer :: ifine,iout,ipout,ipin,iflux,mdomainfill,ipoutfac
     71  integer :: ifine,iout,ipout,ipin,iflux,mdomainfill
    7472  integer :: mquasilag,nested_output,ind_source,ind_receptor
    7573  integer :: ind_rel,ind_samp,ioutputforeachrelease,linit_cond,surf_only
     
    8482  ! iout     output options: 1 conc. output (ng/m3), 2 mixing ratio (pptv), 3 both
    8583  ! ipout    particle dump options: 0 no, 1 every output interval, 2 only at end
    86   ! ipoutfac increase particle dump interval by factor (default 1)
    8784  ! ipin     read in particle positions from dumped file from a previous run
    8885  ! fine     real(ifine)
     
    124121  ! lnetcdfout   1 for netcdf grid output, 0 if not. Set in COMMAND (namelist input)
    125122
    126   integer :: linversionout
    127   ! linversionout 1 for one grid_time output file for each release containing all timesteps
    128 
    129123  integer :: nageclass,lage(maxageclass)
    130124
     
    134128
    135129  logical :: gdomainfill
     130
    136131  ! gdomainfill             .T., if domain-filling is global, .F. if not
    137132
     
    179174  real :: ri(5,numclass),rac(5,numclass),rcl(maxspec,5,numclass)
    180175  real :: rgs(maxspec,5,numclass),rlu(maxspec,5,numclass)
    181   real :: rm(maxspec),dryvel(maxspec),kao(maxspec)
     176  real :: rm(maxspec),dryvel(maxspec)
    182177  real :: ohcconst(maxspec),ohdconst(maxspec),ohnconst(maxspec)
    183178
     
    364359  real :: ciwc(0:nxmax-1,0:nymax-1,nzmax,numwfmem)=0.0 !ice      [kg/kg]
    365360  real :: clw(0:nxmax-1,0:nymax-1,nzmax,numwfmem)=0.0  !combined [m3/m3]
    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)
     361
    369362  real :: pv(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
    370363  real :: rho(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
     
    388381  ! uupol,vvpol [m/s]    wind components in polar stereographic projection
    389382  ! tt [K]               temperature data
    390   ! prs                  air pressure
    391383  ! qv                   specific humidity data
    392384  ! pv (pvu)             potential vorticity
     
    659651  real :: receptorarea(maxreceptor)
    660652  real :: creceptor(maxreceptor,maxspec)
    661   real, allocatable, dimension(:,:) :: creceptor0
    662653  character(len=16) :: receptorname(maxreceptor)
    663654  integer :: numreceptor
     
    682673  real, allocatable, dimension(:,:) :: xmass1
    683674  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
    692675
    693676  ! eso: Moved from timemanager
     
    797780         & idt(nmpart),itramem(nmpart),itrasplit(nmpart),&
    798781         & xtra1(nmpart),ytra1(nmpart),ztra1(nmpart),&
    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
     782         & xmass1(nmpart, maxspec),&
     783         & checklifetime(nmpart,maxspec), species_lifetime(maxspec,2))!CGZ-lifetime
    809784
    810785
    811786    allocate(uap(nmpart),ucp(nmpart),uzp(nmpart),us(nmpart),&
    812787         & vs(nmpart),ws(nmpart),cbt(nmpart))
    813 
     788   
    814789  end subroutine com_mod_allocate_part
    815790
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG