Changeset 38b7917 in flexpart.git for src/init_domainfill.f90


Ignore:
Timestamp:
Mar 8, 2016, 9:54:38 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:
9b53903
Parents:
db712a8
Message:

Parallelization of domain fill option (save/restart not implemented yet)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/init_domainfill.f90

    r8a65cb0 r38b7917  
    2121
    2222subroutine init_domainfill
    23   !
    24   !*****************************************************************************
    25   !                                                                            *
    26   ! Initializes particles equally distributed over the first release location  *
    27   ! specified in file RELEASES. This box is assumed to be the domain for doing *
    28   ! domain-filling trajectory calculations.                                    *
    29   ! All particles carry the same amount of mass which alltogether comprises the*
    30   ! mass of air within the box.                                                *
    31   !                                                                            *
    32   !     Author: A. Stohl                                                       *
    33   !                                                                            *
    34   !     15 October 2002                                                        *
    35   !                                                                            *
    36   !*****************************************************************************
    37   !                                                                            *
    38   ! Variables:                                                                 *
    39   !                                                                            *
    40   ! numparticlecount    consecutively counts the number of particles released  *
    41   ! nx_we(2)       grid indices for western and eastern boundary of domain-    *
    42   !                filling trajectory calculations                             *
    43   ! ny_sn(2)       grid indices for southern and northern boundary of domain-  *
    44   !                filling trajectory calculations                             *
    45   !                                                                            *
    46   !*****************************************************************************
     23!
     24!*****************************************************************************
     25!                                                                            *
     26! Initializes particles equally distributed over the first release location  *
     27! specified in file RELEASES. This box is assumed to be the domain for doing *
     28! domain-filling trajectory calculations.                                    *
     29! All particles carry the same amount of mass which alltogether comprises the*
     30! mass of air within the box.                                                *
     31!                                                                            *
     32!     Author: A. Stohl                                                       *
     33!                                                                            *
     34!     15 October 2002                                                        *
     35!                                                                            *
     36!*****************************************************************************
     37!                                                                            *
     38! Variables:                                                                 *
     39!                                                                            *
     40! numparticlecount    consecutively counts the number of particles released  *
     41! nx_we(2)       grid indices for western and eastern boundary of domain-    *
     42!                filling trajectory calculations                             *
     43! ny_sn(2)       grid indices for southern and northern boundary of domain-  *
     44!                filling trajectory calculations                             *
     45!                                                                            *
     46!*****************************************************************************
    4747
    4848  use point_mod
     
    6565
    6666
    67   ! Determine the release region (only full grid cells), over which particles
    68   ! shall be initialized
    69   ! Use 2 fields for west/east and south/north boundary
    70   !**************************************************************************
     67! Determine the release region (only full grid cells), over which particles
     68! shall be initialized
     69! Use 2 fields for west/east and south/north boundary
     70!**************************************************************************
    7171
    7272  nx_we(1)=max(int(xpoint1(1)),0)
     
    7575  ny_sn(2)=min((int(ypoint2(1))+1),nymin1)
    7676
    77   ! For global simulations (both global wind data and global domain-filling),
    78   ! set a switch, such that no boundary conditions are used
    79   !**************************************************************************
     77! For global simulations (both global wind data and global domain-filling),
     78! set a switch, such that no boundary conditions are used
     79!**************************************************************************
    8080  if (xglobal.and.sglobal.and.nglobal) then
    8181    if ((nx_we(1).eq.0).and.(nx_we(2).eq.nxmin1).and. &
     
    8787  endif
    8888
    89   ! Do not release particles twice (i.e., not at both in the leftmost and rightmost
    90   ! grid cell) for a global domain
    91   !*****************************************************************************
     89! Do not release particles twice (i.e., not at both in the leftmost and rightmost
     90! grid cell) for a global domain
     91!*****************************************************************************
    9292  if (xglobal) nx_we(2)=min(nx_we(2),nx-2)
    9393
    9494
    95   ! Calculate area of grid cell with formula M=2*pi*R*h*dx/360,
    96   ! see Netz, Formeln der Mathematik, 5. Auflage (1983), p.90
    97   !************************************************************
     95! Calculate area of grid cell with formula M=2*pi*R*h*dx/360,
     96! see Netz, Formeln der Mathematik, 5. Auflage (1983), p.90
     97!************************************************************
    9898
    9999  do jy=ny_sn(1),ny_sn(2)      ! loop about latitudes
     
    117117  end do
    118118
    119   ! Do the same for the south pole
     119! Do the same for the south pole
    120120
    121121  if (sglobal) then
     
    130130  endif
    131131
    132   ! Do the same for the north pole
     132! Do the same for the north pole
    133133
    134134  if (nglobal) then
     
    144144
    145145
    146   ! Calculate total mass of each grid column and of the whole atmosphere
    147   !*********************************************************************
     146! Calculate total mass of each grid column and of the whole atmosphere
     147!*********************************************************************
    148148
    149149  colmasstotal=0.
     
    157157  end do
    158158
    159            write(*,*) 'Atm. mass: ',colmasstotal
     159  write(*,*) 'Atm. mass: ',colmasstotal
    160160
    161161
    162162  if (ipin.eq.0) numpart=0
    163163
    164   ! Determine the particle positions
    165   !*********************************
     164! Determine the particle positions
     165!*********************************
    166166
    167167  numparttot=0
     
    175175      if (ncolumn.gt.numcolumn) numcolumn=ncolumn
    176176
    177   ! Calculate pressure at the altitudes of model surfaces, using the air density
    178   ! information, which is stored as a 3-d field
    179   !*****************************************************************************
     177! Calculate pressure at the altitudes of model surfaces, using the air density
     178! information, which is stored as a 3-d field
     179!*****************************************************************************
    180180
    181181      do kz=1,nz
     
    191191
    192192
    193   ! For columns with many particles (i.e. around the equator), distribute
    194   ! the particles equally, for columns with few particles (i.e. around the
    195   ! poles), distribute the particles randomly
    196   !***********************************************************************
     193! For columns with many particles (i.e. around the equator), distribute
     194! the particles equally, for columns with few particles (i.e. around the
     195! poles), distribute the particles randomly
     196!***********************************************************************
    197197
    198198
     
    209209            dz=1./(dz1+dz2)
    210210
    211   ! Assign particle position
    212   !*************************
    213   ! Do the following steps only if particles are not read in from previous model run
    214   !*****************************************************************************
     211! Assign particle position
     212!*************************
     213! Do the following steps only if particles are not read in from previous model run
     214!*****************************************************************************
    215215            if (ipin.eq.0) then
    216216              xtra1(numpart+jj)=real(ix)-0.5+ran1(idummy)
     
    224224
    225225
    226   ! Interpolate PV to the particle position
    227   !****************************************
     226! Interpolate PV to the particle position
     227!****************************************
    228228              ixm=int(xtra1(numpart+jj))
    229229              jym=int(ytra1(numpart+jj))
     
    260260
    261261
    262   ! For domain-filling option 2 (stratospheric O3), do the rest only in the stratosphere
    263   !*****************************************************************************
     262! For domain-filling option 2 (stratospheric O3), do the rest only in the stratosphere
     263!*****************************************************************************
    264264
    265265              if (((ztra1(numpart+jj).gt.3000.).and. &
    266266                   (pvpart.gt.pvcrit)).or.(mdomainfill.eq.1)) then
    267267
    268   ! Assign certain properties to the particle
    269   !******************************************
     268! Assign certain properties to the particle
     269!******************************************
    270270                nclass(numpart+jj)=min(int(ran1(idummy)* &
    271271                     real(nclassunc))+1,nclassunc)
     
    293293  end do
    294294
    295 
    296   ! Check whether numpart is really smaller than maxpart
    297   !*****************************************************
    298 
     295  write(*,*) 'init_domainfill> ncolumn: ', ncolumn
     296  write(*,*) 'init_domainfill> numcolumn: ', numcolumn
     297  write(*,*) 'init_domainfill> ny_sn(1),ny_sn(2): ', ny_sn(1),ny_sn(2)
     298  write(*,*) 'init_domainfill> nx_we(1),nx_we(2): ', nx_we(1),nx_we(2)
     299
     300
     301! Check whether numpart is really smaller than maxpart
     302!*****************************************************
     303
     304! ESO :TODO: this warning need to be moved further up, else out-of-bounds error earlier
    299305  if (numpart.gt.maxpart) then
    300306    write(*,*) 'numpart too large: change source in init_atm_mass.f'
     
    306312
    307313
    308   ! Make sure that all particles are within domain
    309   !***********************************************
     314! Make sure that all particles are within domain
     315!***********************************************
    310316
    311317  do j=1,numpart
     
    319325
    320326
    321   ! For boundary conditions, we need fewer particle release heights per column,
    322   ! because otherwise it takes too long until enough mass has accumulated to
    323   ! release a particle at the boundary (would take dx/u seconds), leading to
    324   ! relatively large position errors of the order of one grid distance.
    325   ! It's better to release fewer particles per column, but to do so more often.
    326   ! Thus, use on the order of nz starting heights per column.
    327   ! We thus repeat the above to determine fewer starting heights, that are
    328   ! used furtheron in subroutine boundcond_domainfill.f.
    329   !****************************************************************************
     327! For boundary conditions, we need fewer particle release heights per column,
     328! because otherwise it takes too long until enough mass has accumulated to
     329! release a particle at the boundary (would take dx/u seconds), leading to
     330! relatively large position errors of the order of one grid distance.
     331! It's better to release fewer particles per column, but to do so more often.
     332! Thus, use on the order of nz starting heights per column.
     333! We thus repeat the above to determine fewer starting heights, that are
     334! used furtheron in subroutine boundcond_domainfill.f.
     335!****************************************************************************
    330336
    331337  fractus=real(numcolumn)/real(nz)
     
    343349
    344350
    345   ! Memorize how many particles per column shall be used for all boundaries
    346   ! This is further used in subroutine boundcond_domainfill.f
    347   ! Use 2 fields for west/east and south/north boundary
    348   !************************************************************************
     351! Memorize how many particles per column shall be used for all boundaries
     352! This is further used in subroutine boundcond_domainfill.f
     353! Use 2 fields for west/east and south/north boundary
     354!************************************************************************
    349355
    350356      if (ix.eq.nx_we(1)) numcolumn_we(1,jy)=ncolumn
     
    353359      if (jy.eq.ny_sn(2)) numcolumn_sn(2,ix)=ncolumn
    354360
    355   ! Calculate pressure at the altitudes of model surfaces, using the air density
    356   ! information, which is stored as a 3-d field
    357   !*****************************************************************************
     361! Calculate pressure at the altitudes of model surfaces, using the air density
     362! information, which is stored as a 3-d field
     363!*****************************************************************************
    358364
    359365      do kz=1,nz
     
    361367      end do
    362368
    363   ! Determine the reference starting altitudes
    364   !*******************************************
     369! Determine the reference starting altitudes
     370!*******************************************
    365371
    366372      deltacol=(pp(1)-pp(nz))/real(ncolumn)
     
    374380            dz=1./(dz1+dz2)
    375381            zposition=(height(kz)*dz2+height(kz+1)*dz1)*dz
    376            if (zposition.gt.height(nz)-0.5) zposition=height(nz)-0.5
    377 
    378   ! Memorize vertical positions where particles are introduced
    379   ! This is further used in subroutine boundcond_domainfill.f
    380   !***********************************************************
     382            if (zposition.gt.height(nz)-0.5) zposition=height(nz)-0.5
     383
     384! Memorize vertical positions where particles are introduced
     385! This is further used in subroutine boundcond_domainfill.f
     386!***********************************************************
    381387
    382388            if (ix.eq.nx_we(1)) zcolumn_we(1,jy,j)=zposition
     
    385391            if (jy.eq.ny_sn(2)) zcolumn_sn(2,ix,j)=zposition
    386392
    387   ! Initialize mass that has accumulated at boundary to zero
    388   !*********************************************************
     393! Initialize mass that has accumulated at boundary to zero
     394!*********************************************************
    389395
    390396            acc_mass_we(1,jy,j)=0.
     
    399405  end do
    400406
    401   ! If particles shall be read in to continue an existing run,
    402   ! then the accumulated masses at the domain boundaries must be read in, too.
    403   ! This overrides any previous calculations.
    404   !***************************************************************************
     407! If particles shall be read in to continue an existing run,
     408! then the accumulated masses at the domain boundaries must be read in, too.
     409! This overrides any previous calculations.
     410!***************************************************************************
    405411
    406412  if (ipin.eq.1) then
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG