Changeset 3719


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)

Location:
palm/trunk/SOURCE
Files:
10 edited

Legend:

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

    r3700 r3719  
    2727! -----------------
    2828! $Id$
     29! Resolved cpu logpoint overlap with all progn.equations, moved cpu_log call
     30! to prognostic_equations for better overview
     31!
     32! 3700 2019-01-26 17:03:42Z knoop
    2933! Some interface calls moved to module_interface + cleanup
    3034!
     
    275279         vl_dim, nvar, nreact,  atol, rtol, nphot, phot_names
    276280
    277     USE cpulog,                                                                                    &
    278          ONLY:  cpu_log, log_point
    279 
    280281    USE chem_modules
    281282
     
    20062007 SUBROUTINE chem_integrate_ij( i, j )
    20072008
    2008     USE cpulog,                                                              &
    2009          ONLY:  cpu_log, log_point
    20102009    USE statistics,                                                          &
    2011          ONLY:  weight_pres
     2010        ONLY:  weight_pres
     2011
    20122012    USE control_parameters,                                                  &
    2013          ONLY:  dt_3d, intermediate_timestep_count, time_since_reference_point
     2013        ONLY:  dt_3d, intermediate_timestep_count, time_since_reference_point
    20142014
    20152015    IMPLICIT NONE
     2016
    20162017    INTEGER,INTENT(IN)       :: i
    20172018    INTEGER,INTENT(IN)       :: j
     
    20512052    REAL(kind=wp)  :: dt_chem                                             
    20522053
    2053     CALL cpu_log( log_point(80), '[chem_integrate_ij]', 'start' )
    2054     !<     set chem_gasphase_on to .FALSE. if you want to skip computation of gas phase chemistry
     2054!
     2055!-- Set chem_gasphase_on to .FALSE. if you want to skip computation of gas phase chemistry
    20552056    IF (chem_gasphase_on) THEN
    20562057       nacc = 0
     
    20982099       cs_time_step = dt_chem
    20992100
    2100        CALL cpu_log( log_point(81), '{chem_gasphase_integrate}', 'start' )
    2101 
    21022101       IF(maxval(rcntrl) > 0.0)   THEN    ! Only if rcntrl is set
    21032102          IF( time_since_reference_point <= 2*dt_3d)  THEN
     
    21132112            icntrl_i = icntrl, rcntrl_i = rcntrl_local, xnacc = nacc, xnrej = nrej, istatus=istatus )
    21142113
    2115        CALL cpu_log( log_point(81), '{chem_gasphase_integrate}', 'stop' )
    2116 
    21172114       DO lsp = 1,nspec
    21182115          chem_species(lsp)%conc (nzb+1:nzt,j,i) = tmp_conc(:,lsp) * tmp_fact_i(:)
     
    21212118
    21222119    ENDIF
    2123     CALL cpu_log( log_point(80), '[chem_integrate_ij]', 'stop' )
    21242120
    21252121    RETURN
  • palm/trunk/SOURCE/disturb_heatflux.f90

    r3655 r3719  
    2525! -----------------
    2626! $Id$
     27! Moved log_points out of subroutine into time_integration for better overview.
     28!
     29! 3655 2019-01-07 16:51:22Z knoop
    2730! unused variable removed
    2831!
     
    112115
    113116
    114     CALL cpu_log( log_point(23), 'disturb_heatflux', 'start' )
    115 
    116117!
    117118!-- Generate random disturbances and store them. Note, if
     
    163164    ENDIF
    164165
    165     CALL cpu_log( log_point(23), 'disturb_heatflux', 'stop' )
    166 
    167166
    168167 END SUBROUTINE disturb_heatflux
  • palm/trunk/SOURCE/large_scale_forcing_nudging_mod.f90

    r3655 r3719  
    2525! -----------------
    2626! $Id$
     27! Removed USE cpulog (unused)
     28!
     29! 3655 2019-01-07 16:51:22Z knoop
    2730! unused variables removed
    2831!
     
    107110               topography, use_subsidence_tendencies
    108111               
    109     USE cpulog,                                                                &
    110         ONLY:  cpu_log, log_point
    111 
    112112    USE grid_variables
    113113
  • palm/trunk/SOURCE/ocean_mod.f90

    r3684 r3719  
    2525! -----------------
    2626! $Id$
     27! Changed log_point to log_point_s, otherwise this overlaps with
     28! 'all progn.equations' cpu measurement.
     29!
     30! 3684 2019-01-20 20:20:58Z knoop
    2731! nopointer option removed
    2832!
     
    14921496
    14931497    USE cpulog,                                                                &
    1494         ONLY:  cpu_log, log_point
     1498        ONLY:  cpu_log, log_point_s
    14951499
    14961500    USE diffusion_s_mod,                                                       &
     
    15291533    IF ( salinity )  THEN
    15301534
    1531        CALL cpu_log( log_point(37), 'sa-equation', 'start' )
     1535       CALL cpu_log( log_point_s(20), 'sa-equation', 'start' )
    15321536
    15331537!
     
    16161620       ENDIF
    16171621
    1618        CALL cpu_log( log_point(37), 'sa-equation', 'stop' )
     1622       CALL cpu_log( log_point_s(20), 'sa-equation', 'stop' )
    16191623
    16201624    ENDIF
     
    16221626!
    16231627!-- Calculate density by the equation of state for seawater
    1624     CALL cpu_log( log_point(38), 'eqns-seawater', 'start' )
     1628    CALL cpu_log( log_point_s(21), 'eqns-seawater', 'start' )
    16251629    CALL eqn_state_seawater
    1626     CALL cpu_log( log_point(38), 'eqns-seawater', 'stop' )
     1630    CALL cpu_log( log_point_s(21), 'eqns-seawater', 'stop' )
    16271631
    16281632 END SUBROUTINE ocean_prognostic_equations
  • palm/trunk/SOURCE/palm.f90

    r3703 r3719  
    2525! -----------------
    2626! $Id$
     27! Included cpu measurement for wall/soil spinup
     28!
     29! 3703 2019-01-29 16:43:53Z knoop
    2730! Some interface calls moved to module_interface + cleanup
    2831!
     
    536539!-- surface model)
    537540    IF ( spinup )  THEN
     541       CALL cpu_log( log_point(41), 'wall/soil spinup', 'start' )
    538542       CALL time_integration_spinup
     543       CALL cpu_log( log_point(41), 'wall/soil spinup', 'stop' )
    539544    ENDIF
    540545
  • palm/trunk/SOURCE/prognostic_equations.f90

    r3684 r3719  
    2525! -----------------
    2626! $Id$
     27! Cleaned up chemistry cpu measurements
     28!
     29! 3684 2019-01-20 20:20:58Z knoop
    2730! OpenACC port for SPEC
    2831!
     
    509512       lsp_usr = 1
    510513!
    511 !--    Chemical reactions
    512        CALL cpu_log( log_point(82), '(chem react + exch_h)', 'start' )
    513  
     514!--    Chemical reactions and deposition
    514515       IF ( chem_gasphase_on ) THEN
    515516!
     
    524525                IF ( intermediate_timestep_count == 1 .OR.                        &
    525526                     call_chem_at_all_substeps )  THEN
     527
     528                   CALL cpu_log( log_point_s(19), 'chem.reactions', 'start' ) 
    526529                   CALL chem_integrate (i,j)
     530                   CALL cpu_log( log_point_s(19), 'chem.reactions', 'stop' )
     531
    527532                   IF ( do_depo )  THEN
     533                      CALL cpu_log( log_point_s(24), 'chem.deposition', 'start' )
    528534                      CALL chem_depo(i,j)
     535                      CALL cpu_log( log_point_s(24), 'chem.deposition', 'stop' )
    529536                   ENDIF
    530537                ENDIF
     
    534541!
    535542!--    Loop over chemical species       
    536        CALL cpu_log( log_point_s(84), 'chemistry exch-horiz ', 'start' )
     543       CALL cpu_log( log_point_s(84), 'chem.exch-horiz', 'start' )
    537544       DO  lsp = 1, nspec
    538545          CALL exchange_horiz( chem_species(lsp)%conc, nbgp )   
     
    550557
    551558       ENDDO
    552        CALL cpu_log( log_point_s(84), 'chemistry exch-horiz ', 'stop' )
    553      
    554        CALL cpu_log( log_point(82), '(chem react + exch_h)', 'stop' )
     559       CALL cpu_log( log_point_s(84), 'chem.exch-horiz', 'stop' )
    555560
    556561    ENDIF       
     
    26112616!-- Calculate prognostic equation for chemical quantites
    26122617    IF ( air_chemistry )  THEN
    2613        CALL cpu_log( log_point(83), '(chem advec+diff+prog)', 'start' )
     2618       CALL cpu_log( log_point_s(25), 'chem.advec+diff+prog', 'start' )
    26142619!
    26152620!--    Loop over chemical species
     
    26222627       ENDDO
    26232628
    2624        CALL cpu_log( log_point(83), '(chem advec+diff+prog)', 'stop' )             
     2629       CALL cpu_log( log_point_s(25), 'chem.advec+diff+prog', 'stop' )             
    26252630    ENDIF   ! Chemicals equations
    26262631       
  • palm/trunk/SOURCE/synthetic_turbulence_generator_mod.f90

    r3646 r3719  
    2525! -----------------
    2626! $Id$
     27! Removed log_point measurement from stg_init, since this part is counted to
     28! log_point(2) 'initialisation' already. Moved other log_points to calls of
     29! the subroutines in time_integration for better overview.
     30!
     31! 3646 2018-12-28 17:58:49Z kanani
    2732! Bugfix: use time_since_reference_point instead of simulated_time (relevant
    2833! when using wall/soil spinup)
     
    182187               syn_turb_gen
    183188
    184     USE cpulog,                                                                &
    185         ONLY:  cpu_log, log_point
    186 
    187189    USE indices,                                                               &
    188190        ONLY:  nbgp, nzb, nzt, nxl, nxlg, nxr, nxrg, nys, nyn, nyng, nysg
     
    573575#endif
    574576
    575     CALL  cpu_log( log_point(57), 'synthetic_turbulence_gen', 'start' )
    576 
    577577#if defined( __parallel )
    578578!
     
    885885    ENDIF
    886886
    887     CALL  cpu_log( log_point(57), 'synthetic_turbulence_gen', 'stop' )
    888 
    889887 END SUBROUTINE stg_init
    890888
     
    10851083    REAL(wp) :: volume_flow_l   !< local mass flux through lateral boundary
    10861084
    1087     CALL  cpu_log( log_point(57), 'synthetic_turbulence_gen', 'start' )
    10881085
    10891086!
     
    14291426    time_stg_call = 0.0_wp
    14301427
    1431     CALL  cpu_log( log_point(57), 'synthetic_turbulence_gen', 'stop' )
    14321428
    14331429 END SUBROUTINE stg_main
     
    18331829    INTEGER(iwp) ::  k
    18341830
    1835     CALL  cpu_log( log_point(57), 'synthetic_turbulence_gen', 'start' )
     1831
    18361832!
    18371833!-- Compute mean boundary layer height according to Richardson-Bulk
     
    18671863    time_stg_adjust = 0.0_wp
    18681864   
    1869     CALL  cpu_log( log_point(57), 'synthetic_turbulence_gen', 'stop' )
    18701865   
    18711866 END SUBROUTINE stg_adjust
  • 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
  • palm/trunk/SOURCE/time_integration_spinup.f90

    r3655 r3719  
    2525! -----------------
    2626! $Id$
     27! Removed log_point(19,54,74,50,75), since they count together with same log
     28! points in time_integration, impossible to separate the contributions.
     29! Instead, the entire spinup gets an individual log_point in palm.f90
     30!
     31! 3655 2019-01-07 16:51:22Z knoop
    2732! Removed call to calculation of near air (10 cm) potential temperature (now in
    2833! surface layer fluxes)
     
    360365!--          (constant flux) layer are computed
    361366             IF ( constant_flux_layer )  THEN
    362                 CALL cpu_log( log_point(19), 'surface_layer_fluxes', 'start' )
    363367                CALL surface_layer_fluxes
    364                 CALL cpu_log( log_point(19), 'surface_layer_fluxes', 'stop' )
    365368             ENDIF
    366369
     
    371374             IF ( land_surface )  THEN
    372375
    373                 CALL cpu_log( log_point(54), 'land_surface', 'start' )
    374376!
    375377!--             Call for horizontal upward-facing surfaces
     
    392394                CALL lsm_energy_balance( .FALSE., 3 )
    393395                CALL lsm_soil_model( .FALSE., 3, calc_soil_moisture_during_spinup )
    394                
    395                 CALL cpu_log( log_point(54), 'land_surface', 'stop' )
     396
    396397             ENDIF
    397398
     
    400401!--          the material heat model
    401402             IF (urban_surface) THEN
    402                 CALL cpu_log( log_point(74), 'urban_surface', 'start' )
     403
    403404                CALL usm_surface_energy_balance( .TRUE. )
    404405                IF ( usm_material_model )  THEN
     
    406407                   CALL usm_material_heat_model( .TRUE. )
    407408                ENDIF
    408                
    409                 CALL cpu_log( log_point(74), 'urban_surface', 'stop' )
     409
    410410             ENDIF
    411411
     
    422422             THEN
    423423
    424                 CALL cpu_log( log_point(50), 'radiation', 'start' )
    425 
    426424                IF ( .NOT. force_radiation_call )  THEN
    427425                   time_radiation = time_radiation - dt_3d
     
    430428                CALL radiation_control
    431429
    432                 CALL cpu_log( log_point(50), 'radiation', 'stop' )
    433 
    434430                IF ( radiation_interactions )  THEN
    435                    CALL cpu_log( log_point(75), 'radiation_interaction', 'start' )
    436431                   CALL radiation_interaction
    437                    CALL cpu_log( log_point(75), 'radiation_interaction', 'stop' )
    438432                ENDIF
    439433             ENDIF
  • palm/trunk/SOURCE/turbulence_closure_mod.f90

    r3684 r3719  
    2525! -----------------
    2626! $Id$
     27! Changed log_point to log_point_s, otherwise this overlaps with
     28! 'all progn.equations' cpu measurement.
     29!
     30! 3684 2019-01-20 20:20:58Z knoop
    2731! Remove unused variable simulated_time
    2832!
     
    214218
    215219    USE cpulog,                                                                &
    216         ONLY:  cpu_log, log_point, log_point_s
     220        ONLY:  cpu_log, log_point_s
    217221
    218222    USE indices,                                                               &
     
    19451949    IF ( .NOT. constant_diffusion )  THEN
    19461950
    1947        CALL cpu_log( log_point(16), 'tke-equation', 'start' )
     1951       CALL cpu_log( log_point_s(16), 'tke-equation', 'start' )
    19481952
    19491953       sbt = tsc(2)
     
    20532057       ENDIF
    20542058
    2055        CALL cpu_log( log_point(16), 'tke-equation', 'stop' )
     2059       CALL cpu_log( log_point_s(16), 'tke-equation', 'stop' )
    20562060
    20572061    ENDIF   ! TKE equation
     
    20612065    IF ( rans_tke_e )  THEN
    20622066
    2063        CALL cpu_log( log_point(33), 'diss-equation', 'start' )
     2067       CALL cpu_log( log_point_s(33), 'diss-equation', 'start' )
    20642068
    20652069       sbt = tsc(2)
     
    21532157       ENDIF
    21542158
    2155        CALL cpu_log( log_point(33), 'diss-equation', 'stop' )
     2159       CALL cpu_log( log_point_s(33), 'diss-equation', 'stop' )
    21562160
    21572161    ENDIF
Note: See TracChangeset for help on using the changeset viewer.