Ignore:
Timestamp:
Feb 6, 2019 1:10:18 PM (5 years ago)
Author:
kanani
Message:

Correct and clean-up cpu_logs, some overlapping counts (chemistry_model_mod, disturb_heatflux, large_scale_forcing_nudging_mod, ocean_mod, palm, prognostic_equations, synthetic_turbulence_generator_mod, time_integration, time_integration_spinup, turbulence_closure_mod)

File:
1 edited

Legend:

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

    r3705 r3719  
    2525! -----------------
    2626! $Id$
     27! - removed wind_turbine cpu measurement, since same time is measured inside
     28!   wtm_forces subroutine as special measures
     29! - moved the numerous vnest cpulog to special measures
     30! - extended radiation cpulog over entire radiation part,
     31!   moved radiation_interactions cpulog to special measures
     32! - moved some cpu_log calls to this routine for better overview
     33!
     34! 3705 2019-01-29 19:56:39Z suehring
    2735! Data output for virtual measurements added
    2836!
     
    795803       IF ( vnested ) THEN
    796804          IF ( .NOT. vnest_init  .AND.  simulated_time >= vnest_start_time )  THEN
    797              CALL cpu_log( log_point(80), 'vnest_init', 'start' )
     805             CALL cpu_log( log_point_s(22), 'vnest_init', 'start' )
    798806             CALL vnest_init_fine
    799807             vnest_init = .TRUE.
    800              CALL cpu_log( log_point(80), 'vnest_init', 'stop' )
     808             CALL cpu_log( log_point_s(22), 'vnest_init', 'stop' )
    801809          ENDIF
    802810       ENDIF
     
    841849!
    842850!--    Calculate forces by wind turbines
    843        IF ( wind_turbine )  THEN
    844 
    845           CALL cpu_log( log_point(55), 'wind_turbine', 'start' )
    846 
    847           CALL wtm_forces
    848 
    849           CALL cpu_log( log_point(55), 'wind_turbine', 'stop' )
    850 
    851        ENDIF   
     851       IF ( wind_turbine )  CALL wtm_forces 
    852852       
    853853!
     
    10491049!--       Vertical nesting: Interpolate fine grid data to the coarse grid
    10501050          IF ( vnest_init ) THEN
    1051              CALL cpu_log( log_point(81), 'vnest_anterpolate', 'start' )
     1051             CALL cpu_log( log_point_s(37), 'vnest_anterpolate', 'start' )
    10521052             CALL vnest_anterpolate
    1053              CALL cpu_log( log_point(81), 'vnest_anterpolate', 'stop' )
     1053             CALL cpu_log( log_point_s(37), 'vnest_anterpolate', 'stop' )
    10541054          ENDIF
    10551055
     
    11251125!
    11261126!--       Impose a turbulent inflow using the recycling method
    1127           IF ( turbulent_inflow )  CALL  inflow_turbulence
     1127          IF ( turbulent_inflow )  CALL inflow_turbulence
    11281128
    11291129!
    11301130!--       Set values at outflow boundary using the special outflow condition
    1131           IF ( turbulent_outflow )  CALL  outflow_turbulence
     1131          IF ( turbulent_outflow )  CALL outflow_turbulence
    11321132
    11331133!
     
    11701170!--       only once per time step.
    11711171          IF ( use_syn_turb_gen  .AND.  time_stg_call >= dt_stg_call  .AND.    &
    1172              intermediate_timestep_count == intermediate_timestep_count_max )  THEN! &
     1172             intermediate_timestep_count == intermediate_timestep_count_max )  THEN
     1173             CALL cpu_log( log_point(57), 'synthetic_turbulence_gen', 'start' )
    11731174             CALL stg_main
     1175             CALL cpu_log( log_point(57), 'synthetic_turbulence_gen', 'stop' )
    11741176          ENDIF
    11751177!
     
    11911193                IF ( coupling_mode == 'vnested_crse' )  CALL pres
    11921194
    1193                 CALL cpu_log( log_point(82), 'vnest_bc', 'start' )
     1195                CALL cpu_log( log_point_s(30), 'vnest_bc', 'start' )
    11941196                CALL vnest_boundary_conds
    1195                 CALL cpu_log( log_point(82), 'vnest_bc', 'stop' )
     1197                CALL cpu_log( log_point_s(30), 'vnest_bc', 'stop' )
    11961198 
    11971199                IF ( coupling_mode == 'vnested_fine' )  CALL pres
    11981200
    11991201!--             Anterpolate TKE, satisfy Germano Identity
    1200                 CALL cpu_log( log_point(83), 'vnest_anter_e', 'start' )
     1202                CALL cpu_log( log_point_s(28), 'vnest_anter_e', 'start' )
    12011203                CALL vnest_anterpolate_e
    1202                 CALL cpu_log( log_point(83), 'vnest_anter_e', 'stop' )
     1204                CALL cpu_log( log_point_s(28), 'vnest_anter_e', 'stop' )
    12031205
    12041206             ELSE
     
    13471349                CALL radiation_control
    13481350
    1349                 CALL cpu_log( log_point(50), 'radiation', 'stop' )
    1350 
    13511351                IF ( ( urban_surface  .OR.  land_surface )  .AND.               &
    13521352                     radiation_interactions )  THEN
    1353                    CALL cpu_log( log_point(75), 'radiation_interaction', 'start' )
     1353                   CALL cpu_log( log_point_s(75), 'radiation_interaction', 'start' )
    13541354                   CALL radiation_interaction
    1355                    CALL cpu_log( log_point(75), 'radiation_interaction', 'stop' )
     1355                   CALL cpu_log( log_point_s(75), 'radiation_interaction', 'stop' )
    13561356                ENDIF
    13571357   
     
    13591359!--             Return the current time to its original value
    13601360                time_since_reference_point = time_since_reference_point_save
     1361
     1362                CALL cpu_log( log_point(50), 'radiation', 'stop' )
    13611363
    13621364             ENDIF
     
    14771479          IF ( parametrize_inflow_turbulence )  THEN
    14781480             time_stg_adjust = time_stg_adjust + dt_3d
    1479              IF ( time_stg_adjust >= dt_stg_adjust )  CALL stg_adjust
     1481             IF ( time_stg_adjust >= dt_stg_adjust )  THEN
     1482                CALL cpu_log( log_point(57), 'synthetic_turbulence_gen', 'start' )
     1483                CALL stg_adjust
     1484                CALL cpu_log( log_point(57), 'synthetic_turbulence_gen', 'stop' )
     1485             ENDIF
    14801486          ENDIF
    14811487          time_stg_call = time_stg_call + dt_3d
     
    17451751
    17461752!
    1747 !--    If required, set the heat flux for the next time step at a random value
     1753!--    If required, set the heat flux for the next time step to a random value
    17481754       IF ( constant_heatflux  .AND.  random_heatflux )  THEN
    1749           IF ( surf_def_h(0)%ns >= 1 )  CALL disturb_heatflux( surf_def_h(0) )
    1750           IF ( surf_lsm_h%ns    >= 1 )  CALL disturb_heatflux( surf_lsm_h    )
    1751           IF ( surf_usm_h%ns    >= 1 )  CALL disturb_heatflux( surf_usm_h    )
     1755          IF ( surf_def_h(0)%ns >= 1 )  THEN
     1756             CALL cpu_log( log_point(23), 'disturb_heatflux', 'start' )
     1757             CALL disturb_heatflux( surf_def_h(0) )
     1758             CALL cpu_log( log_point(23), 'disturb_heatflux', 'stop' )
     1759          ENDIF
     1760          IF ( surf_lsm_h%ns    >= 1 )  THEN
     1761             CALL cpu_log( log_point(23), 'disturb_heatflux', 'start' )
     1762             CALL disturb_heatflux( surf_lsm_h    )
     1763             CALL cpu_log( log_point(23), 'disturb_heatflux', 'stop' )
     1764          ENDIF
     1765          IF ( surf_usm_h%ns    >= 1 )  THEN
     1766             CALL cpu_log( log_point(23), 'disturb_heatflux', 'start' )
     1767             CALL disturb_heatflux( surf_usm_h    )
     1768             CALL cpu_log( log_point(23), 'disturb_heatflux', 'stop' )
     1769          ENDIF
    17521770       ENDIF
    17531771
Note: See TracChangeset for help on using the changeset viewer.