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/flow_statistics.f90

    r700 r709  
    44! Current revisions:
    55! -----------------
     6! formatting adjustments
    67!
    78! Former revisions:
     
    114115    USE arrays_3d
    115116    USE cloud_parameters
     117    USE control_parameters
    116118    USE cpulog
    117119    USE grid_variables
     
    120122    USE pegrid
    121123    USE statistics
    122     USE control_parameters
    123124
    124125    IMPLICIT NONE
     
    738739          ENDDO
    739740       ENDDO
    740 !-     for reasons of speed optimization the loop is splitted, to avoid if-else
    741 !-     statements inside the loop
    742 !-     Fluxes which have been computed in part directly inside the advection routines
    743 !-     treated seperatly.
    744 !-     First treat the momentum fluxes
     741!
     742!--    For speed optimization fluxes which have been computed in part directly
     743!--    inside the WS advection routines are treated seperatly
     744!--    Momentum fluxes first:
    745745       IF ( .NOT. ws_scheme_mom )  THEN
    746746         !$OMP DO
     
    771771         DO  i = nxl, nxr
    772772            DO  j = nys, nyn
    773                DO  k = nzb_diff_s_inner(j,i) - 1, nzt_diff
    774 !-                vertical heat flux
     773               DO  k = nzb_diff_s_inner(j,i)-1, nzt_diff
     774!
     775!--               Vertical heat flux
    775776                  sums_l(k,17,tn) = sums_l(k,17,tn) +  0.5 * &
    776777                           ( pt(k,j,i)   - hom(k,1,4,sr) + &
     
    12211222
    12221223 END SUBROUTINE flow_statistics
    1223 
    1224 
    1225 
Note: See TracChangeset for help on using the changeset viewer.