Changeset b0434e1 in flexpart.git for src/com_mod.f90


Ignore:
Timestamp:
Feb 4, 2016, 9:38:22 AM (8 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, univie
Children:
db712a8
Parents:
9484483
Message:

Initial code to handle cloud water in nested wind fields (it is not completely implemented in this commit)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/com_mod.f90

    rfddc6ec rb0434e1  
    138138
    139139!NIK 16.02.2015
    140   integer :: tot_blc_count=0, tot_inc_count=0
    141 
     140  integer(selected_int_kind(16)) :: tot_blc_count=0, tot_inc_count=0
    142141
    143142
     
    487486  !*****************
    488487
    489   real :: uun(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
    490   real :: vvn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
    491   real :: wwn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
    492   real :: ttn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
    493   real :: qvn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
    494   real :: pvn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
    495   integer(kind=1) :: cloudsn(0:nxmaxn-1,0:nymaxn-1,0:nzmax,numwfmem,maxnests)
    496   integer :: cloudsnh(0:nxmaxn-1,0:nymaxn-1,numwfmem,maxnests)
    497   real :: rhon(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
    498   real :: drhodzn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
    499   real :: tthn(0:nxmaxn-1,0:nymaxn-1,nuvzmax,numwfmem,maxnests)
    500   real :: qvhn(0:nxmaxn-1,0:nymaxn-1,nuvzmax,numwfmem,maxnests)
     488  real,allocatable,dimension(:,:,:,:,:) :: uun, vvn, wwn, ttn, qvn, pvn,&
     489       & rhon, drhodzn, tthn, qvhn
     490  integer,allocatable,dimension(:,:,:,:) :: cloudsnh
     491  integer(kind=1),allocatable,dimension(:,:,:,:,:) :: cloudsn
    501492
    502493  ! 2d nested fields
     
    752743  integer :: mpi_mode=0 ! .gt. 0 if running MPI version
    753744  logical :: lroot=.true. ! true if serial version, or if MPI .and. root process
    754 
    755   contains
    756       subroutine com_mod_allocate(nmpart)
    757 !*******************************************************************************   
    758 ! Dynamic allocation of arrays
    759 !
    760 ! For FLEXPART version 9.2 and earlier these arrays were statically declared
    761 ! with size maxpart. This function is introduced so that the MPI version
    762 ! can declare these arrays with smaller size ("maxpart per process"), while
    763 ! the serial version allocate at run-time with size maxpart
    764 !
    765 !*******************************************************************************
     745 
     746contains
     747  subroutine com_mod_allocate_part(nmpart)
     748  !*******************************************************************************   
     749  ! Dynamic allocation of arrays
     750  !
     751  ! For FLEXPART version 9.2 and earlier these arrays were statically declared
     752  ! with size maxpart. This function is introduced so that the MPI version
     753  ! can declare these arrays with smaller size ("maxpart per process"), while
     754  ! the serial version allocate at run-time with size maxpart
     755  !
     756  !*******************************************************************************
    766757    implicit none
    767758
     
    779770         & vs(nmpart),ws(nmpart),cbt(nmpart))
    780771   
    781   end subroutine com_mod_allocate
     772  end subroutine com_mod_allocate_part
     773
     774
     775  subroutine com_mod_allocate_nests
     776  !*******************************************************************************   
     777  ! Dynamic allocation of arrays
     778  !
     779  ! For nested wind fields.
     780  !
     781  !*******************************************************************************
     782    implicit none
     783
     784    allocate(uun(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,numbnests))
     785    allocate(vvn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,numbnests))
     786    allocate(wwn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,numbnests))
     787    allocate(ttn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,numbnests))
     788    allocate(qvn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,numbnests))
     789    allocate(pvn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,numbnests))
     790    allocate(cloudsn(0:nxmaxn-1,0:nymaxn-1,0:nzmax,numwfmem,numbnests))
     791    allocate(cloudsnh(0:nxmaxn-1,0:nymaxn-1,numwfmem,numbnests))
     792    allocate(rhon(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,numbnests))
     793    allocate(drhodzn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,numbnests))
     794    allocate(tthn(0:nxmaxn-1,0:nymaxn-1,nuvzmax,numwfmem,numbnests))
     795    allocate(qvhn(0:nxmaxn-1,0:nymaxn-1,nuvzmax,numwfmem,numbnests))
     796
     797   
     798  end subroutine com_mod_allocate_nests
    782799   
    783800
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG