Ignore:
Timestamp:
Oct 7, 2015 11:56:08 PM (9 years ago)
Author:
knoop
Message:

Code annotations made doxygen readable

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/lpm_boundary_conds.f90

    r1360 r1682  
    1  SUBROUTINE lpm_boundary_conds( range )
    2 
     1!> @file lpm_boundary_conds.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    5251! Description:
    5352! ------------
    54 ! Boundary conditions for the Lagrangian particles.
    55 ! The routine consists of two different parts. One handles the bottom (flat)
    56 ! and top boundary. In this part, also particles which exceeded their lifetime
    57 ! are deleted.
    58 ! The other part handles the reflection of particles from vertical walls.
    59 ! This part was developed by Jin Zhang during 2006-2007.
    60 !
    61 ! To do: Code structure for finding the t_index values and for checking the
    62 ! -----  reflection conditions is basically the same for all four cases, so it
    63 !        should be possible to further simplify/shorten it.
    64 !
    65 ! THE WALLS PART OF THIS ROUTINE HAS NOT BEEN TESTED FOR OCEAN RUNS SO FAR!!!!
    66 ! (see offset_ocean_*)
     53!> Boundary conditions for the Lagrangian particles.
     54!> The routine consists of two different parts. One handles the bottom (flat)
     55!> and top boundary. In this part, also particles which exceeded their lifetime
     56!> are deleted.
     57!> The other part handles the reflection of particles from vertical walls.
     58!> This part was developed by Jin Zhang during 2006-2007.
     59!>
     60!> To do: Code structure for finding the t_index values and for checking the
     61!> -----  reflection conditions is basically the same for all four cases, so it
     62!>        should be possible to further simplify/shorten it.
     63!>
     64!> THE WALLS PART OF THIS ROUTINE HAS NOT BEEN TESTED FOR OCEAN RUNS SO FAR!!!!
     65!> (see offset_ocean_*)
    6766!------------------------------------------------------------------------------!
     67 SUBROUTINE lpm_boundary_conds( range )
     68 
    6869
    6970    USE arrays_3d,                                                             &
     
    9495    IMPLICIT NONE
    9596
    96     CHARACTER (LEN=*) ::  range     !:
     97    CHARACTER (LEN=*) ::  range     !<
    9798   
    98     INTEGER(iwp) ::  i              !:
    99     INTEGER(iwp) ::  inc            !:
    100     INTEGER(iwp) ::  ir             !:
    101     INTEGER(iwp) ::  i1             !:
    102     INTEGER(iwp) ::  i2             !:
    103     INTEGER(iwp) ::  i3             !:
    104     INTEGER(iwp) ::  i5             !:
    105     INTEGER(iwp) ::  j              !:
    106     INTEGER(iwp) ::  jr             !:
    107     INTEGER(iwp) ::  j1             !:
    108     INTEGER(iwp) ::  j2             !:
    109     INTEGER(iwp) ::  j3             !:
    110     INTEGER(iwp) ::  j5             !:
    111     INTEGER(iwp) ::  k              !:
    112     INTEGER(iwp) ::  k1             !:
    113     INTEGER(iwp) ::  k2             !:
    114     INTEGER(iwp) ::  k3             !:
    115     INTEGER(iwp) ::  k5             !:
    116     INTEGER(iwp) ::  n              !:
    117     INTEGER(iwp) ::  nn             !:
    118     INTEGER(iwp) ::  t_index        !:
    119     INTEGER(iwp) ::  t_index_number !:
     99    INTEGER(iwp) ::  i              !<
     100    INTEGER(iwp) ::  inc            !<
     101    INTEGER(iwp) ::  ir             !<
     102    INTEGER(iwp) ::  i1             !<
     103    INTEGER(iwp) ::  i2             !<
     104    INTEGER(iwp) ::  i3             !<
     105    INTEGER(iwp) ::  i5             !<
     106    INTEGER(iwp) ::  j              !<
     107    INTEGER(iwp) ::  jr             !<
     108    INTEGER(iwp) ::  j1             !<
     109    INTEGER(iwp) ::  j2             !<
     110    INTEGER(iwp) ::  j3             !<
     111    INTEGER(iwp) ::  j5             !<
     112    INTEGER(iwp) ::  k              !<
     113    INTEGER(iwp) ::  k1             !<
     114    INTEGER(iwp) ::  k2             !<
     115    INTEGER(iwp) ::  k3             !<
     116    INTEGER(iwp) ::  k5             !<
     117    INTEGER(iwp) ::  n              !<
     118    INTEGER(iwp) ::  nn             !<
     119    INTEGER(iwp) ::  t_index        !<
     120    INTEGER(iwp) ::  t_index_number !<
    120121   
    121     LOGICAL  ::  reflect_x   !:
    122     LOGICAL  ::  reflect_y   !:
    123     LOGICAL  ::  reflect_z   !:
    124 
    125     REAL(wp) ::  dt_particle !:
    126     REAL(wp) ::  pos_x       !:
    127     REAL(wp) ::  pos_x_old   !:
    128     REAL(wp) ::  pos_y       !:
    129     REAL(wp) ::  pos_y_old   !:
    130     REAL(wp) ::  pos_z       !:
    131     REAL(wp) ::  pos_z_old   !:
    132     REAL(wp) ::  prt_x       !:
    133     REAL(wp) ::  prt_y       !:
    134     REAL(wp) ::  prt_z       !:
    135     REAL(wp) ::  t(1:200)    !:
    136     REAL(wp) ::  tmp_t       !:
    137     REAL(wp) ::  xline       !:
    138     REAL(wp) ::  yline       !:
    139     REAL(wp) ::  zline       !:
     122    LOGICAL  ::  reflect_x   !<
     123    LOGICAL  ::  reflect_y   !<
     124    LOGICAL  ::  reflect_z   !<
     125
     126    REAL(wp) ::  dt_particle !<
     127    REAL(wp) ::  pos_x       !<
     128    REAL(wp) ::  pos_x_old   !<
     129    REAL(wp) ::  pos_y       !<
     130    REAL(wp) ::  pos_y_old   !<
     131    REAL(wp) ::  pos_z       !<
     132    REAL(wp) ::  pos_z_old   !<
     133    REAL(wp) ::  prt_x       !<
     134    REAL(wp) ::  prt_y       !<
     135    REAL(wp) ::  prt_z       !<
     136    REAL(wp) ::  t(1:200)    !<
     137    REAL(wp) ::  tmp_t       !<
     138    REAL(wp) ::  xline       !<
     139    REAL(wp) ::  yline       !<
     140    REAL(wp) ::  zline       !<
    140141
    141142    IF ( range == 'bottom/top' )  THEN
Note: See TracChangeset for help on using the changeset viewer.