Ignore:
Timestamp:
Jun 4, 2007 8:07:41 AM (17 years ago)
Author:
raasch
Message:

more preliminary uncomplete changes for ocean version

File:
1 edited

Legend:

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

    r77 r96  
    44! Actual revisions:
    55! -----------------
    6 !
     6! calc_mean_pt_profile renamed calc_mean_profile
    77!
    88! Former revisions:
     
    2929
    3030    PRIVATE
    31     PUBLIC buoyancy, calc_mean_pt_profile
     31    PUBLIC buoyancy, calc_mean_profile
    3232
    3333    INTERFACE buoyancy
     
    3636    END INTERFACE buoyancy
    3737
    38     INTERFACE calc_mean_pt_profile
    39        MODULE PROCEDURE calc_mean_pt_profile
    40     END INTERFACE calc_mean_pt_profile
     38    INTERFACE calc_mean_profile
     39       MODULE PROCEDURE calc_mean_profile
     40    END INTERFACE calc_mean_profile
    4141
    4242 CONTAINS
     
    207207
    208208
    209     SUBROUTINE calc_mean_pt_profile( theta, pr )
     209    SUBROUTINE calc_mean_profile( var, pr )
    210210
    211211!------------------------------------------------------------------------------!
     
    224224
    225225       INTEGER ::  i, j, k, omp_get_thread_num, pr, tn
    226        REAL, DIMENSION(:,:,:), POINTER  ::  theta
    227 
    228 !
    229 !--    Computation of the horizontally averaged temperature profile, unless
     226       REAL, DIMENSION(:,:,:), POINTER  ::  var
     227
     228!
     229!--    Computation of the horizontally averaged profile of variable var, unless
    230230!--    already done by the relevant call from flow_statistics. The calculation
    231231!--    is done only for the first respective intermediate timestep in order to
    232232!--    spare communication time and to produce identical model results with jobs
    233233!--    which are calling flow_statistics at different time intervals.
    234 !--    Although this calculation is not required for model runs with a slope,
    235 !--    it is nevertheless also computed.
    236234       IF ( .NOT. flow_statistics_called  .AND. &
    237235            intermediate_timestep_count == 1 )  THEN
    238236
    239237!
    240 !--       Horizontal average of the potential temperature
     238!--       Horizontal average of variable var
    241239          tn           =   0  ! Default thread number in case of one thread
    242240          !$OMP PARALLEL PRIVATE( i, j, k, tn )
     
    247245             DO  j =  nys, nyn
    248246                DO  k = nzb_s_outer(j,i), nzt+1
    249                    sums_l(k,pr,tn) = sums_l(k,pr,tn) + theta(k,j,i)
     247                   sums_l(k,pr,tn) = sums_l(k,pr,tn) + var(k,j,i)
    250248                ENDDO
    251249             ENDDO
     
    272270       ENDIF
    273271
    274     END SUBROUTINE calc_mean_pt_profile
     272    END SUBROUTINE calc_mean_profile
    275273
    276274 END MODULE buoyancy_mod
Note: See TracChangeset for help on using the changeset viewer.