Ignore:
Timestamp:
Mar 30, 2011 9:31:40 AM (13 years ago)
Author:
raasch
Message:

formatting adjustments

File:
1 edited

Legend:

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

    r708 r709  
    44! Current revisions:
    55! -----------------
    6 !
     6! formatting adjustments
    77!
    88! Former revisions:
     
    104104
    105105    ddt_3d = 1.0 / dt_3d
    106     d_weight_pres = 1. / weight_pres(intermediate_timestep_count)
     106    d_weight_pres = 1.0 / weight_pres(intermediate_timestep_count)
    107107
    108108!
     
    146146!
    147147!-- Left/right
    148 
    149     IF ( conserve_volume_flow  .AND.  ( outflow_l  .OR. outflow_r ) )  THEN
     148    IF ( conserve_volume_flow  .AND.  ( outflow_l .OR. outflow_r ) )  THEN
    150149
    151150       volume_flow(1)   = 0.0
     
    161160!
    162161!--       Sum up the volume flow through the south/north boundary
    163           DO  k = nzb_2d(j,i) + 1, nzt
     162          DO  k = nzb_2d(j,i)+1, nzt
    164163             volume_flow_l(1) = volume_flow_l(1) + u(k,j,i) * dzw(k)
    165164          ENDDO
     
    173172       volume_flow = volume_flow_l 
    174173#endif
    175        volume_flow_offset(1) = ( volume_flow_initial(1) - volume_flow(1) )    &
     174       volume_flow_offset(1) = ( volume_flow_initial(1) - volume_flow(1) ) &
    176175                               / volume_flow_area(1)
    177176
    178177       DO  j = nysg, nyng
    179           DO  k = nzb_2d(j,i) + 1, nzt
     178          DO  k = nzb_2d(j,i)+1, nzt
    180179             u(k,j,i) = u(k,j,i) + volume_flow_offset(1)
    181180          ENDDO
     
    186185!
    187186!-- South/north
    188     IF ( conserve_volume_flow  .AND.  ( outflow_n  .OR. outflow_s ) )  THEN
     187    IF ( conserve_volume_flow  .AND.  ( outflow_n .OR. outflow_s ) )  THEN
    189188
    190189       volume_flow(2)   = 0.0
     
    200199!
    201200!--       Sum up the volume flow through the south/north boundary
    202           DO  k = nzb_2d(j,i) + 1, nzt
     201          DO  k = nzb_2d(j,i)+1, nzt
    203202             volume_flow_l(2) = volume_flow_l(2) + v(k,j,i) * dzw(k)
    204203          ENDDO
     
    216215
    217216       DO  i = nxlg, nxrg
    218           DO  k = nzb_v_inner(j,i) + 1, nzt
     217          DO  k = nzb_v_inner(j,i)+1, nzt
    219218             v(k,j,i) = v(k,j,i) + volume_flow_offset(2)
    220219          ENDDO
     
    226225!-- Remove mean vertical velocity
    227226    IF ( ibc_p_b == 1  .AND.  ibc_p_t == 1 )  THEN
    228        IF ( simulated_time > 0.0 )  THEN ! otherwise nzb_w_inner is not yet known
     227       IF ( simulated_time > 0.0 )  THEN ! otherwise nzb_w_inner not yet known
    229228          w_l = 0.0;  w_l_l = 0.0
    230229          DO  i = nxl, nxr
     
    237236#if defined( __parallel )   
    238237          IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    239           CALL MPI_ALLREDUCE( w_l_l(1), w_l(1), nzt, MPI_REAL, MPI_SUM, comm2d, &
    240                               ierr )
     238          CALL MPI_ALLREDUCE( w_l_l(1), w_l(1), nzt, MPI_REAL, MPI_SUM, &
     239                              comm2d, ierr )
    241240#else
    242241          w_l = w_l_l 
     
    574573!-- Correction of the provisional velocities with the current perturbation
    575574!-- pressure just computed
    576     IF ( conserve_volume_flow  .AND.  ( bc_lr_cyc  .OR. bc_ns_cyc ) )  THEN
     575    IF ( conserve_volume_flow  .AND.  ( bc_lr_cyc .OR. bc_ns_cyc ) )  THEN
    577576       volume_flow_l(1) = 0.0
    578577       volume_flow_l(2) = 0.0
Note: See TracChangeset for help on using the changeset viewer.