Ignore:
Timestamp:
May 22, 2019 9:52:13 AM (5 years ago)
Author:
kanani
Message:

clean up location, debug and error messages

File:
1 edited

Legend:

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

    r3956 r3987  
    2525! -----------------
    2626! $Id$
     27! Introduce switchable DEBUG file output via debug_message routine
     28!
     29! 3956 2019-05-07 12:32:52Z monakurppa
    2730! - Added calls for salsa_non_advective_processes and
    2831!   salsa_exchange_horiz_bounds
     
    122125!-- ToDo: move all of them to respective module or a dedicated central module
    123126    USE control_parameters,                                                    &
    124         ONLY:  biometeorology,                                                 &
    125                air_chemistry,                                                  &
     127        ONLY:  air_chemistry,                                                  &
     128               biometeorology,                                                 &
     129               debug_output,                                                   &
     130               debug_output_timestep,                                          &
    126131               indoor_model,                                                   &
    127132               land_surface,                                                   &
     
    539544
    540545
     546    IF ( debug_output )  CALL debug_message( 'reading module-specific parameters', 'start' )
     547
    541548    CALL bio_parin
    542549    CALL bcm_parin
     
    563570    CALL package_parin ! ToDo: deprecated, needs to be dissolved
    564571
     572    IF ( debug_output )  CALL debug_message( 'reading module-specific parameters', 'end' )
     573
    565574
    566575 END SUBROUTINE module_interface_parin
     
    574583 SUBROUTINE module_interface_check_parameters
    575584
     585
     586    IF ( debug_output )  CALL debug_message( 'checking module-specific parameters', 'start' )
    576587
    577588    IF ( bulk_cloud_model )     CALL bcm_check_parameters
     
    594605    IF ( user_module_enabled )  CALL user_check_parameters
    595606
     607    IF ( debug_output )  CALL debug_message( 'checking module-specific parameters', 'end' )
     608
    596609
    597610 END SUBROUTINE module_interface_check_parameters
     
    612625
    613626
     627    IF ( debug_output )  CALL debug_message( 'checking module-specific data output ts', 'start' )
     628
    614629    IF ( radiation )  THEN
    615630       CALL radiation_check_data_output_ts( dots_max, dots_num )
     
    619634       CALL user_check_data_output_ts( dots_max, dots_num, dots_label, dots_unit )
    620635    ENDIF
     636
     637    IF ( debug_output )  CALL debug_message( 'checking module-specific data output ts', 'end' )
    621638
    622639
     
    638655    CHARACTER (LEN=*), INTENT(OUT)   ::  dopr_unit !< local value of dopr_unit
    639656
     657
     658    IF ( debug_output )  CALL debug_message( 'checking module-specific data output pr', 'start' )
     659
    640660    IF ( unit == 'illegal' .AND.  bulk_cloud_model )  THEN
    641661       CALL bcm_check_data_output_pr( variable, var_count, unit, dopr_unit )
     
    670690       CALL user_check_data_output_pr( variable, var_count, unit, dopr_unit )
    671691    ENDIF
     692
     693    IF ( debug_output )  CALL debug_message( 'checking module-specific data output pr', 'end' )
    672694
    673695
     
    690712    INTEGER(iwp),      INTENT(IN)    :: k         !< ToDo: remove dummy argument, instead pass string from data_output
    691713
     714
     715    IF ( debug_output )  CALL debug_message( 'checking module-specific data output 2d/3d', 'start' )
     716
    692717    IF ( unit == 'illegal'  .AND.  biometeorology )  THEN
    693718       CALL bio_check_data_output( variable, unit, i, j, ilen, k )
     
    742767    ENDIF
    743768
     769    IF ( debug_output )  CALL debug_message( 'checking module-specific data output 2d/3d', 'end' )
     770
    744771
    745772 END SUBROUTINE module_interface_check_data_output
     
    757784    CHARACTER (LEN=*), INTENT(IN)    ::  variable !< variable name
    758785    CHARACTER (LEN=*), INTENT(INOUT) ::  unit     !< physical unit of variable
     786
     787
     788    IF ( debug_output )  CALL debug_message( 'initializing module-specific masks', 'start' )
    759789
    760790    IF ( unit == 'illegal'  .AND.  air_chemistry                               &
     
    775805       CALL user_check_data_output( variable, unit )
    776806    ENDIF
     807
     808    IF ( debug_output )  CALL debug_message( 'initializing module-specific masks', 'end' )
    777809
    778810
     
    795827    CHARACTER (LEN=*), INTENT(OUT) ::  grid_y !< netcdf dimension in y-direction
    796828    CHARACTER (LEN=*), INTENT(OUT) ::  grid_z !< netcdf dimension in z-direction
     829
     830
     831    IF ( debug_output )  CALL debug_message( 'defining module-specific netcdf grids', 'start' )
    797832!
    798833!-- As long as no action is done in this subroutine, initialize strings with
     
    806841    IF ( var == ' ' )  RETURN
    807842
     843    IF ( debug_output )  CALL debug_message( 'defining module-specific netcdf grids', 'end' )
     844
     845
    808846 END SUBROUTINE module_interface_define_netcdf_grid
    809847
     
    817855
    818856
    819     CALL location_message( 'initializing module-specific arrays', 'start' )
     857    IF ( debug_output )  CALL debug_message( 'initializing module-specific arrays', 'start' )
    820858
    821859    IF ( bulk_cloud_model    )  CALL bcm_init_arrays
     
    830868    IF ( user_module_enabled )  CALL user_init_arrays
    831869
    832     CALL location_message( 'initializing module-specific arrays', 'finished' )
     870    IF ( debug_output )  CALL debug_message( 'initializing module-specific arrays', 'end' )
    833871
    834872
     
    844882
    845883
    846     CALL location_message( 'initializing module features', 'start' )
     884    IF ( debug_output )  CALL debug_message( 'module-specific initialization', 'start' )
    847885
    848886    IF ( biometeorology      )  CALL bio_init
     
    864902    IF ( user_module_enabled )  CALL user_init
    865903
    866     CALL location_message( 'initializing module features', 'finished' )
     904    IF ( debug_output )  CALL debug_message( 'module-specific initialization', 'end' )
    867905
    868906
     
    878916
    879917
     918    IF ( debug_output )  CALL debug_message( 'module-specific post-initialization checks', 'start' )
     919
    880920    IF ( biometeorology      )  CALL bio_init_checks
    881921
     922    IF ( debug_output )  CALL debug_message( 'module-specific post-initialization checks', 'end' )
     923
    882924
    883925 END SUBROUTINE module_interface_init_checks
     
    894936    INTEGER(iwp), INTENT(IN) ::  io  !< unit of the output file
    895937
     938
     939    IF ( debug_output )  CALL debug_message( 'module-specific header output', 'start' )
    896940
    897941    IF ( biometeorology      )  CALL bio_header ( io )
     
    911955    IF ( user_module_enabled )  CALL user_header( io )
    912956
     957    IF ( debug_output )  CALL debug_message( 'module-specific header output', 'end' )
     958
    913959
    914960 END SUBROUTINE module_interface_header
     
    9661012! Description:
    9671013! ------------
    968 !> Compute module-specificc non_advective_processes (vector-optimized)
     1014!> Compute module-specific non_advective_processes (vector-optimized)
    9691015!------------------------------------------------------------------------------!
    9701016 SUBROUTINE module_interface_non_advective_processes()
     
    10061052
    10071053
     1054    IF ( debug_output_timestep )  CALL debug_message( 'module-specific exchange_horiz', 'start' )
     1055
    10081056    IF ( bulk_cloud_model    )  CALL bcm_exchange_horiz()
    10091057    IF ( air_chemistry       )  CALL chem_exchange_horiz_bounds()
    10101058    IF ( salsa               )  CALL salsa_exchange_horiz_bounds()
     1059
     1060    IF ( debug_output_timestep )  CALL debug_message( 'module-specific exchange_horiz', 'end' )
     1061
    10111062
    10121063 END SUBROUTINE module_interface_exchange_horiz
     
    10641115
    10651116    INTEGER(iwp), INTENT(IN) :: swap_mode !< determines procedure of pointer swap
     1117
     1118
     1119    IF ( debug_output_timestep )  CALL debug_message( 'module-specific swap timelevel', 'start' )
    10661120
    10671121    IF ( bulk_cloud_model    )  CALL bcm_swap_timelevel( swap_mode )
     
    10731127    IF ( urban_surface       )  CALL usm_swap_timelevel( swap_mode )
    10741128
     1129    IF ( debug_output_timestep )  CALL debug_message( 'module-specific swap timelevel', 'end' )
     1130
    10751131
    10761132 END SUBROUTINE module_interface_swap_timelevel
     
    10881144    CHARACTER (LEN=*), INTENT(IN) ::  mode     !< averaging interface mode
    10891145    CHARACTER (LEN=*), INTENT(IN) ::  variable !< variable name
     1146
     1147
     1148    IF ( debug_output_timestep )  CALL debug_message( 'module-specific 3d data averaging', 'start' )
    10901149
    10911150    IF ( biometeorology      )  CALL bio_3d_data_averaging( mode, variable )
     
    11001159    IF ( user_module_enabled )  CALL user_3d_data_averaging( mode, variable )
    11011160
     1161    IF ( debug_output_timestep )  CALL debug_message( 'module-specific 3d data averaging', 'end' )
     1162
    11021163
    11031164 END SUBROUTINE module_interface_3d_data_averaging
     
    11261187
    11271188
     1189    IF ( debug_output_timestep )  CALL debug_message( 'module-specific 2d data output', 'start' )
     1190
    11281191    IF ( .NOT. found  .AND.  biometeorology )  THEN
    11291192       CALL bio_data_output_2d(                                                &
     
    11791242            )
    11801243    ENDIF
     1244
     1245    IF ( debug_output_timestep )  CALL debug_message( 'module-specific 2d data output', 'end' )
     1246
    11811247
    11821248 END SUBROUTINE module_interface_data_output_2d
     
    12041270
    12051271
     1272    IF ( debug_output_timestep )  CALL debug_message( 'module-specific 3d data output', 'start' )
     1273
    12061274    IF ( .NOT. found  .AND.  biometeorology )  THEN
    12071275       CALL bio_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
     
    12541322    ENDIF
    12551323
     1324    IF ( debug_output_timestep )  CALL debug_message( 'module-specific 3d data output', 'end' )
     1325
    12561326
    12571327 END SUBROUTINE module_interface_data_output_3d
     
    12711341    INTEGER(iwp),      INTENT(IN) ::  dots_max !< maximum number of timeseries
    12721342
     1343
     1344    IF ( debug_output_timestep )  CALL debug_message( 'module-specific statistics', 'start' )
     1345
    12731346    IF ( gust_module_enabled )  CALL gust_statistics( mode, sr, tn, dots_max )
    12741347    IF ( air_chemistry       )  CALL chem_statistics( mode, sr, tn )
    12751348    IF ( user_module_enabled )  CALL user_statistics( mode, sr, tn )
    12761349
     1350    IF ( debug_output_timestep )  CALL debug_message( 'module-specific statistics', 'end' )
     1351
    12771352
    12781353 END SUBROUTINE module_interface_statistics
     
    12881363
    12891364    LOGICAL, INTENT(INOUT) ::  found    !< flag if variable was found
     1365
     1366
     1367    IF ( debug_output )  CALL debug_message( 'module-specific read global restart data', 'start' )
    12901368
    12911369    IF ( .NOT. found )  CALL bio_rrd_global( found ) ! ToDo: change interface to pass variable
     
    12991377    IF ( .NOT. found )  CALL user_rrd_global( found ) ! ToDo: change interface to pass variable
    13001378
     1379    IF ( debug_output )  CALL debug_message( 'module-specific read global restart data', 'end' )
     1380
    13011381
    13021382 END SUBROUTINE module_interface_rrd_global
     
    13101390 SUBROUTINE module_interface_wrd_global
    13111391
     1392
     1393    IF ( debug_output )  CALL debug_message( 'module-specific write global restart data', 'start' )
    13121394
    13131395    IF ( biometeorology )       CALL bio_wrd_global
     
    13201402    IF ( surface_output )       CALL surface_data_output_wrd_global
    13211403    IF ( user_module_enabled )  CALL user_wrd_global
     1404
     1405    IF ( debug_output )  CALL debug_message( 'module-specific write global restart data', 'end' )
    13221406
    13231407
     
    13571441
    13581442
     1443    IF ( debug_output )  CALL debug_message( 'module-specific read local restart data', 'start' )
     1444
    13591445    IF ( .NOT. found ) CALL bio_rrd_local(                                     &
    13601446                               found                                           &
     
    14451531                            ) ! ToDo: change interface to pass variable
    14461532
     1533    IF ( debug_output )  CALL debug_message( 'module-specific read local restart data', 'end' )
     1534
    14471535
    14481536 END SUBROUTINE module_interface_rrd_local
     
    14561544 SUBROUTINE module_interface_wrd_local
    14571545
     1546
     1547    IF ( debug_output )  CALL debug_message( 'module-specific write local restart data', 'start' )
    14581548
    14591549    IF ( biometeorology )       CALL bio_wrd_local
     
    14691559    IF ( user_module_enabled )  CALL user_wrd_local
    14701560
     1561    IF ( debug_output )  CALL debug_message( 'module-specific write local restart data', 'end' )
     1562
    14711563
    14721564 END SUBROUTINE module_interface_wrd_local
     
    14801572 SUBROUTINE module_interface_last_actions
    14811573
     1574
     1575    IF ( debug_output )  CALL debug_message( 'module-specific last actions', 'start' )
    14821576
    14831577    IF ( virtual_measurement )  CALL vm_last_actions
    14841578    IF ( user_module_enabled )  CALL user_last_actions
    14851579
     1580    IF ( debug_output )  CALL debug_message( 'module-specific last actions', 'end' )
     1581
    14861582
    14871583 END SUBROUTINE module_interface_last_actions
Note: See TracChangeset for help on using the changeset viewer.