Ignore:
Timestamp:
Mar 11, 2007 11:50:04 AM (17 years ago)
Author:
raasch
Message:

preliminary update of further changes, running

File:
1 edited

Legend:

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

    r58 r60  
    1616! Routine developed by Jin Zhang (2006-2007)
    1717!------------------------------------------------------------------------------!
    18 #if defined( __particles )
    1918
    2019    USE control_parameters
     
    2827    IMPLICIT NONE
    2928
    30     INTEGER ::  n
    31 
     29    INTEGER ::  i, inc, ir, i1, i2, i3, i5, j, jr, j1, j2, j3, j5, k, k1, k2, &
     30                k3, k5, n, t_index, t_index_number
     31
     32    REAL ::  dt_particle, pos_x, pos_x_old, pos_y, pos_y_old, pos_z, &
     33             pos_z_old, prt_x, prt_y, prt_z, tmp_t, xline, yline, zline
     34
     35    REAL ::  t(1:200)
    3236
    3337    CALL cpu_log( log_point_s(48), 'advec_part_refle', 'start' )
     
    3640
    3741    DO  n = 1, number_of_particles
     42
     43       dt_particle = particles(n)%age - particles(n)%age_m
    3844
    3945       i2 = ( particles(n)%x + 0.5 * dx ) * ddx
Note: See TracChangeset for help on using the changeset viewer.