Changeset 8a65cb0 in flexpart.git for src/com_mod.f90


Ignore:
Timestamp:
Mar 2, 2015, 3:11:55 PM (9 years ago)
Author:
Espen Sollum ATMOS <espen@…>
Branches:
master, 10.4.1_pesei, GFS_025, bugfixes+enhancements, dev, release-10, release-10.4.1, scaling-bug, univie
Children:
1d207bb
Parents:
60403cd
Message:

Added code, makefile for dev branch

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/com_mod.f90

    re92a713 r8a65cb0  
    1515  use par_mod, only: dp, numpath, maxnests, maxageclass, maxspec, ni, &
    1616       numclass, nymax, nxmax, maxcolumn, maxwf, nzmax, nxmaxn, nymaxn, &
    17        maxreceptor, maxpart, maxrand, nwzmax, nuvzmax
     17       maxreceptor, maxpart, maxrand, nwzmax, nuvzmax, numwfmem
    1818
    1919  implicit none
     
    2323  !****************************************************************
    2424
    25   character :: path(numpath+2*maxnests)*256
     25  character :: path(numpath+2*maxnests)*120
    2626  integer :: length(numpath+2*maxnests)
    2727  character(len=256) :: pathfile, flexversion, arg1, arg2
     
    7070  integer :: ind_rel,ind_samp,ioutputforeachrelease,linit_cond,surf_only
    7171  logical :: turbswitch
     72  integer :: cblflag  !added by mc for cbl
    7273
    7374  ! ctl      factor, by which time step must be smaller than Lagrangian time scale
     
    100101
    101102  ! ind_rel and ind_samp  are used within the code to change between mass and mass-mix (see readcommand.f)
     103  ! cblflag !: 1 activate cbl skewed pdf routines with bi-gaussina pdf whan OL<0 added by mc
    102104
    103105
     
    113115  ! lagespectra  1 if age spectra calculation switched on, 2 if not
    114116
     117  integer :: lnetcdfout
     118  ! lnetcdfout   1 for netcdf grid output, 0 if not. Set in COMMAND (namelist input)
    115119
    116120  integer :: nageclass,lage(maxageclass)
     
    123127
    124128  ! gdomainfill             .T., if domain-filling is global, .F. if not
     129
     130!hg
     131  logical :: readclouds
     132
     133!NIK 16.02.2015
     134  integer :: tot_blc_count, tot_inc_count
    125135
    126136
     
    145155  real :: weta(maxspec),wetb(maxspec)
    146156! NIK: 31.01.2013- parameters for in-cloud scavening
    147   real :: weta_in(maxspec), wetb_in(maxspec), wetc_in(maxspec), wetd_in(maxspec)
     157  real :: weta_in(maxspec), wetb_in(maxspec)
    148158  real :: reldiff(maxspec),henry(maxspec),f0(maxspec)
    149159  real :: density(maxspec),dquer(maxspec),dsigma(maxspec)
     
    152162  real :: ri(5,numclass),rac(5,numclass),rcl(maxspec,5,numclass)
    153163  real :: rgs(maxspec,5,numclass),rlu(maxspec,5,numclass)
    154   real :: rm(maxspec),dryvel(maxspec),kao(maxspec),ohreact(maxspec)
     164  real :: rm(maxspec),dryvel(maxspec),kao(maxspec)
     165  real :: ohcconst(maxspec),ohdconst(maxspec)
    155166  ! se  it is possible to associate a species with a second one to make transfer from gas to aerosol
    156167  integer :: spec_ass(maxspec)
     
    256267  ! wfname(maxwf)           file names of wind fields
    257268  ! wfspec(maxwf)           specifications of wind field file, e.g. if on hard
    258   !                    disc or on tape
    259 
    260   integer :: memtime(2),memind(2)
     269  !                         disc or on tape
     270
     271  integer :: memtime(numwfmem),memind(numwfmem) ! eso: or memind(3) and change
     272                                                ! interpol_rain
    261273
    262274  ! memtime [s]             validation times of wind fields in memory
    263275  ! memind                  pointer to wind field, in order to avoid shuffling
    264   !                    of wind fields
     276  !                         of wind fields
    265277
    266278
     
    327339  !**********
    328340
    329   real :: uu(0:nxmax-1,0:nymax-1,nzmax,2)
    330   real :: vv(0:nxmax-1,0:nymax-1,nzmax,2)
    331   real :: uupol(0:nxmax-1,0:nymax-1,nzmax,2)
    332   real :: vvpol(0:nxmax-1,0:nymax-1,nzmax,2)
    333   real :: ww(0:nxmax-1,0:nymax-1,nzmax,2)
    334   real :: tt(0:nxmax-1,0:nymax-1,nzmax,2)
    335   real :: qv(0:nxmax-1,0:nymax-1,nzmax,2)
    336   real :: pv(0:nxmax-1,0:nymax-1,nzmax,2)
    337   real :: rho(0:nxmax-1,0:nymax-1,nzmax,2)
    338   real :: drhodz(0:nxmax-1,0:nymax-1,nzmax,2)
    339   real :: tth(0:nxmax-1,0:nymax-1,nuvzmax,2)
    340   real :: qvh(0:nxmax-1,0:nymax-1,nuvzmax,2)
    341   real :: pplev(0:nxmax-1,0:nymax-1,nuvzmax,2)
    342   integer(kind=1) :: clouds(0:nxmax-1,0:nymax-1,nzmax,2)
    343   integer :: cloudsh(0:nxmax-1,0:nymax-1,2)
     341  real :: uu(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
     342  real :: vv(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
     343  real :: uupol(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
     344  real :: vvpol(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
     345  real :: ww(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
     346  real :: tt(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
     347  real :: qv(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
     348!hg adding cloud water
     349  real :: clwc(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
     350  real :: ciwc(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
     351  real :: pv(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
     352  real :: rho(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
     353  real :: drhodz(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
     354  real :: tth(0:nxmax-1,0:nymax-1,nuvzmax,numwfmem)
     355  real :: qvh(0:nxmax-1,0:nymax-1,nuvzmax,numwfmem)
     356  real :: clwch(0:nxmax-1,0:nymax-1,nuvzmax,numwfmem)
     357  real :: ciwch(0:nxmax-1,0:nymax-1,nuvzmax,numwfmem)
     358
     359  real :: pplev(0:nxmax-1,0:nymax-1,nuvzmax,numwfmem)
     360  !scavenging NIK, PS
     361  integer(kind=1) :: clouds(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
     362  integer :: cloudsh(0:nxmax-1,0:nymax-1,numwfmem)
     363  ! integer :: icloudbot(0:nxmax-1,0:nymax-1,numwfmem)
     364  ! integer :: icloudthck(0:nxmax-1,0:nymax-1,numwfmem)
    344365
    345366
     
    356377  !      rainout  conv/lsp dominated  2/3
    357378  !      washout  conv/lsp dominated  4/5
     379  ! PS 2013
     380  !c icloudbot (m)        cloud bottom height
     381  !c icloudthck (m)       cloud thickness     
    358382
    359383  ! pplev for the GFS version
     
    362386  !**********
    363387
    364   real :: ps(0:nxmax-1,0:nymax-1,1,2)
    365   real :: sd(0:nxmax-1,0:nymax-1,1,2)
    366   real :: msl(0:nxmax-1,0:nymax-1,1,2)
    367   real :: tcc(0:nxmax-1,0:nymax-1,1,2)
    368   real :: u10(0:nxmax-1,0:nymax-1,1,2)
    369   real :: v10(0:nxmax-1,0:nymax-1,1,2)
    370   real :: tt2(0:nxmax-1,0:nymax-1,1,2)
    371   real :: td2(0:nxmax-1,0:nymax-1,1,2)
    372   real :: lsprec(0:nxmax-1,0:nymax-1,1,2)
    373   real :: convprec(0:nxmax-1,0:nymax-1,1,2)
    374   real :: sshf(0:nxmax-1,0:nymax-1,1,2)
    375   real :: ssr(0:nxmax-1,0:nymax-1,1,2)
    376   real :: surfstr(0:nxmax-1,0:nymax-1,1,2)
    377   real :: ustar(0:nxmax-1,0:nymax-1,1,2)
    378   real :: wstar(0:nxmax-1,0:nymax-1,1,2)
    379   real :: hmix(0:nxmax-1,0:nymax-1,1,2)
    380   real :: tropopause(0:nxmax-1,0:nymax-1,1,2)
    381   real :: oli(0:nxmax-1,0:nymax-1,1,2)
    382   real :: diffk(0:nxmax-1,0:nymax-1,1,2)
     388  real :: ps(0:nxmax-1,0:nymax-1,1,numwfmem)
     389  real :: sd(0:nxmax-1,0:nymax-1,1,numwfmem)
     390  real :: msl(0:nxmax-1,0:nymax-1,1,numwfmem)
     391  real :: tcc(0:nxmax-1,0:nymax-1,1,numwfmem)
     392  real :: u10(0:nxmax-1,0:nymax-1,1,numwfmem)
     393  real :: v10(0:nxmax-1,0:nymax-1,1,numwfmem)
     394  real :: tt2(0:nxmax-1,0:nymax-1,1,numwfmem)
     395  real :: td2(0:nxmax-1,0:nymax-1,1,numwfmem)
     396  real :: lsprec(0:nxmax-1,0:nymax-1,1,numwfmem)
     397  real :: convprec(0:nxmax-1,0:nymax-1,1,numwfmem)
     398  real :: sshf(0:nxmax-1,0:nymax-1,1,numwfmem)
     399  real :: ssr(0:nxmax-1,0:nymax-1,1,numwfmem)
     400  real :: surfstr(0:nxmax-1,0:nymax-1,1,numwfmem)
     401  real :: ustar(0:nxmax-1,0:nymax-1,1,numwfmem)
     402  real :: wstar(0:nxmax-1,0:nymax-1,1,numwfmem)
     403  real :: hmix(0:nxmax-1,0:nymax-1,1,numwfmem)
     404  real :: tropopause(0:nxmax-1,0:nymax-1,1,numwfmem)
     405  real :: oli(0:nxmax-1,0:nymax-1,1,numwfmem)
     406! real :: diffk(0:nxmax-1,0:nymax-1,1,numwfmem) this is not in use?
    383407
    384408  ! ps                   surface pressure
     
    403427
    404428
    405   real :: vdep(0:nxmax-1,0:nymax-1,maxspec,2)
     429  real :: vdep(0:nxmax-1,0:nymax-1,maxspec,numwfmem)
    406430
    407431  ! vdep [m/s]           deposition velocities
     
    453477  !*****************
    454478
    455   real :: uun(0:nxmaxn-1,0:nymaxn-1,nzmax,2,maxnests)
    456   real :: vvn(0:nxmaxn-1,0:nymaxn-1,nzmax,2,maxnests)
    457   real :: wwn(0:nxmaxn-1,0:nymaxn-1,nzmax,2,maxnests)
    458   real :: ttn(0:nxmaxn-1,0:nymaxn-1,nzmax,2,maxnests)
    459   real :: qvn(0:nxmaxn-1,0:nymaxn-1,nzmax,2,maxnests)
    460   real :: pvn(0:nxmaxn-1,0:nymaxn-1,nzmax,2,maxnests)
    461   integer(kind=1) :: cloudsn(0:nxmaxn-1,0:nymaxn-1,0:nzmax,2,maxnests)
    462   integer :: cloudsnh(0:nxmaxn-1,0:nymaxn-1,2,maxnests)
    463   real :: rhon(0:nxmaxn-1,0:nymaxn-1,nzmax,2,maxnests)
    464   real :: drhodzn(0:nxmaxn-1,0:nymaxn-1,nzmax,2,maxnests)
    465   real :: tthn(0:nxmaxn-1,0:nymaxn-1,nuvzmax,2,maxnests)
    466   real :: qvhn(0:nxmaxn-1,0:nymaxn-1,nuvzmax,2,maxnests)
     479  real :: uun(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
     480  real :: vvn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
     481  real :: wwn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
     482  real :: ttn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
     483  real :: qvn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
     484  real :: pvn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
     485  integer(kind=1) :: cloudsn(0:nxmaxn-1,0:nymaxn-1,0:nzmax,numwfmem,maxnests)
     486  integer :: cloudsnh(0:nxmaxn-1,0:nymaxn-1,numwfmem,maxnests)
     487  real :: rhon(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
     488  real :: drhodzn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
     489  real :: tthn(0:nxmaxn-1,0:nymaxn-1,nuvzmax,numwfmem,maxnests)
     490  real :: qvhn(0:nxmaxn-1,0:nymaxn-1,nuvzmax,numwfmem,maxnests)
    467491
    468492  ! 2d nested fields
    469493  !*****************
    470494
    471   real :: psn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests)
    472   real :: sdn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests)
    473   real :: msln(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests)
    474   real :: tccn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests)
    475   real :: u10n(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests)
    476   real :: v10n(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests)
    477   real :: tt2n(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests)
    478   real :: td2n(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests)
    479   real :: lsprecn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests)
    480   real :: convprecn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests)
    481   real :: sshfn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests)
    482   real :: ssrn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests)
    483   real :: surfstrn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests)
    484   real :: ustarn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests)
    485   real :: wstarn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests)
    486   real :: hmixn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests)
    487   real :: tropopausen(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests)
    488   real :: olin(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests)
    489   real :: diffkn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests)
    490   real :: vdepn(0:nxmaxn-1,0:nymaxn-1,maxspec,2,maxnests)
     495  real :: psn(0:nxmaxn-1,0:nymaxn-1,1,numwfmem,maxnests)
     496  real :: sdn(0:nxmaxn-1,0:nymaxn-1,1,numwfmem,maxnests)
     497  real :: msln(0:nxmaxn-1,0:nymaxn-1,1,numwfmem,maxnests)
     498  real :: tccn(0:nxmaxn-1,0:nymaxn-1,1,numwfmem,maxnests)
     499  real :: u10n(0:nxmaxn-1,0:nymaxn-1,1,numwfmem,maxnests)
     500  real :: v10n(0:nxmaxn-1,0:nymaxn-1,1,numwfmem,maxnests)
     501  real :: tt2n(0:nxmaxn-1,0:nymaxn-1,1,numwfmem,maxnests)
     502  real :: td2n(0:nxmaxn-1,0:nymaxn-1,1,numwfmem,maxnests)
     503  real :: lsprecn(0:nxmaxn-1,0:nymaxn-1,1,numwfmem,maxnests)
     504  real :: convprecn(0:nxmaxn-1,0:nymaxn-1,1,numwfmem,maxnests)
     505  real :: sshfn(0:nxmaxn-1,0:nymaxn-1,1,numwfmem,maxnests)
     506  real :: ssrn(0:nxmaxn-1,0:nymaxn-1,1,numwfmem,maxnests)
     507  real :: surfstrn(0:nxmaxn-1,0:nymaxn-1,1,numwfmem,maxnests)
     508  real :: ustarn(0:nxmaxn-1,0:nymaxn-1,1,numwfmem,maxnests)
     509  real :: wstarn(0:nxmaxn-1,0:nymaxn-1,1,numwfmem,maxnests)
     510  real :: hmixn(0:nxmaxn-1,0:nymaxn-1,1,numwfmem,maxnests)
     511  real :: tropopausen(0:nxmaxn-1,0:nymaxn-1,1,numwfmem,maxnests)
     512  real :: olin(0:nxmaxn-1,0:nymaxn-1,1,numwfmem,maxnests)
     513  ! real :: diffkn(0:nxmaxn-1,0:nymaxn-1,1,numwfmem,maxnests) ! not in use?
     514  real :: vdepn(0:nxmaxn-1,0:nymaxn-1,maxspec,numwfmem,maxnests)
    491515
    492516
     
    628652  !***************************************
    629653
    630   integer :: numpart,itra1(maxpart)
    631   integer :: npoint(maxpart),nclass(maxpart)
    632   integer :: idt(maxpart),itramem(maxpart),itrasplit(maxpart)
     654  integer :: numpart=0
    633655  integer :: numparticlecount
    634656
    635   real(kind=dp) :: xtra1(maxpart),ytra1(maxpart)
    636   real :: ztra1(maxpart),xmass1(maxpart,maxspec)
     657  integer, allocatable, dimension(:) :: itra1, npoint, nclass, idt, itramem, itrasplit
     658
     659  real(kind=dp), allocatable, dimension(:) :: xtra1, ytra1
     660  real, allocatable, dimension(:) :: ztra1
     661  real, allocatable, dimension(:,:) :: xmass1
     662
     663  ! eso: Moved from timemanager
     664  real, allocatable, dimension(:) :: uap,ucp,uzp,us,vs,ws
     665  integer(kind=2), allocatable, dimension(:) :: cbt
     666
    637667
    638668  ! numpart                 actual number of particles in memory
     
    646676  ! xtra1,ytra1,ztra1       spatial positions of the particles
    647677  ! xmass1 [kg]             particle masses
    648 
     678 
    649679
    650680
     
    680710
    681711  ! rannumb                 field of normally distributed random numbers
     712 
     713  !********************************************************************
     714  ! variables to control stability of CBL scheme under variation
     715  ! of statistics in time and space
     716  !********************************************************************
     717  integer :: nan_count,nan_count2,sum_nan_count(3600),maxtl=1200
     718  !added by mc , note that for safety sum_nan_count(N) with N>maxtl
     719
     720  !********************************************************************
     721  ! variables to test well-mixed state of CBL scheme not to be included in final release
     722  !********************************************************************
     723  real :: well_mixed_vector(50),h_well,well_mixed_norm,avg_air_dens(50),avg_ol,avg_wst,avg_h
     724  ! modified by mc to test well-mixed for cbl
    682725
    683726  !********************
     
    686729  integer :: verbosity=0
    687730  integer :: info_flag=0
    688   integer :: time_flag=0
    689   integer :: debug_flag=0
    690731  integer :: count_clock, count_clock0,  count_rate, count_max
    691   logical :: nmlout=.true.
     732  real    :: tins
     733  logical, parameter :: nmlout=.false.
     734
     735  ! These variables are used to avoid having separate versions of
     736  ! files in cases where differences with MPI version is minor (eso)
     737  !*****************************************************************
     738  integer :: mpi_mode=0 ! .gt. 0 if running MPI version
     739  logical :: lroot=.true. ! true if serial version, or if MPI and root process
     740
     741  contains
     742      subroutine com_mod_allocate(nmpart)
     743!*******************************************************************************   
     744! Dynamic allocation of arrays
     745!
     746!*******************************************************************************
     747    implicit none
     748
     749    integer, intent(in) :: nmpart
     750   
     751! Arrays previously static of size maxpart
     752    allocate(itra1(nmpart),npoint(nmpart),nclass(nmpart),&
     753         & idt(nmpart),itramem(nmpart),itrasplit(nmpart),&
     754         & xtra1(nmpart),ytra1(nmpart),ztra1(nmpart),&
     755         & xmass1(nmpart, maxspec))
     756
     757    allocate(uap(nmpart),ucp(nmpart),uzp(nmpart),us(nmpart),&
     758         & vs(nmpart),ws(nmpart),cbt(nmpart))
     759   
     760!    allocate(memind(
     761
     762  end subroutine com_mod_allocate
    692763   
    693764
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG