Ignore:
Timestamp:
Apr 11, 2019 11:29:34 AM (5 years ago)
Author:
kanani
Message:

restructure/add location/debug messages

File:
1 edited

Legend:

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

    r3883 r3885  
    2525! -----------------
    2626! $Id$
     27! Changes related to global restructuring of location messages and introduction
     28! of additional debug messages
     29!
     30! 3883 2019-04-10 12:51:50Z hellstea
    2731! Checks and error messages improved and extended. All the child index bounds in the
    2832! parent-grid index space are made module variables. Function get_number_of_childs
     
    405409               bc_dirichlet_s, child_domain,                                   &
    406410               constant_diffusion, constant_flux_layer,                        &
    407                coupling_char, dt_3d, dz, humidity, message_string,             &
     411               coupling_char,                                                  &
     412               debug_output, debug_string,                                     &
     413               dt_3d, dz, humidity, message_string,                            &
    408414               neutral, passive_scalar, rans_mode, rans_tke_e,                 &
    409415               roughness_length, salsa, topography, volume_flow
     
    790796!-- Attention: myid has been set at the end of pmc_init_model in order to
    791797!-- guarantee that only PE0 of the root domain does the output.
    792     CALL location_message( 'finished', .TRUE. )
     798    CALL location_message( 'initialize model nesting', 'finished' )
    793799!
    794800!-- Reset myid to its default value
     
    800806!-- world_comm is given a dummy value to avoid compiler warnings (INTENT(OUT)
    801807!-- should get an explicit value)
     808!-- todo: why don't we print an error message instead of these settings?
    802809    cpl_id     = 1
    803810    nested_run = .FALSE.
     
    817824   
    818825#if defined( __parallel )
    819     CALL location_message( 'setup the nested model configuration', .FALSE. )
     826    CALL location_message( 'setup the nested model configuration', 'start' )
    820827    CALL cpu_log( log_point_s(79), 'pmci_model_config', 'start' )
    821828!
     
    844851
    845852    CALL cpu_log( log_point_s(79), 'pmci_model_config', 'stop' )
    846     CALL location_message( 'finished', .TRUE. )
     853    CALL location_message( 'setup the nested model configuration', 'finished' )
    847854#endif
    848855
     
    30503057   REAL(wp) ::  dtg       !<  Global time step defined as the global minimum of dtl of all processes
    30513058
     3059    IF ( debug_output )  THEN
     3060       WRITE( debug_string, * ) 'pmci_synchronize'
     3061       CALL debug_message( debug_string, 'start' )
     3062    ENDIF
    30523063   
    30533064   dtl = dt_3d
    30543065   CALL MPI_ALLREDUCE( dtl, dtg, 1, MPI_REAL, MPI_MIN, MPI_COMM_WORLD, ierr )
    30553066   dt_3d  = dtg
     3067
     3068    IF ( debug_output )  THEN
     3069       WRITE( debug_string, * ) 'pmci_synchronize'
     3070       CALL debug_message( debug_string, 'end' )
     3071    ENDIF
    30563072
    30573073#endif
     
    30993115    CHARACTER(LEN=*), INTENT(IN) ::  local_nesting_mode  !<  Nesting mode: 'one-way', 'two-way' or 'vertical'
    31003116
     3117!
     3118!-- Debug location message
     3119    IF ( debug_output )  THEN
     3120       WRITE( debug_string, * ) 'pmci_datatrans'
     3121       CALL debug_message( debug_string, 'start' )
     3122    ENDIF
    31013123
    31023124    IF ( TRIM( local_nesting_mode ) == 'one-way' )  THEN
     
    31333155       ENDIF
    31343156
     3157    ENDIF
     3158!
     3159!-- Debug location message
     3160    IF ( debug_output )  THEN
     3161       WRITE( debug_string, * ) 'pmci_datatrans'
     3162       CALL debug_message( debug_string, 'end' )
    31353163    ENDIF
    31363164
     
    46004628    INTEGER(iwp) ::  n   !< Running index for number of chemical species
    46014629   
     4630!
     4631!-- Debug location message
     4632    IF ( debug_output )  THEN
     4633       WRITE( debug_string, * ) 'pmci_boundary_conds'
     4634       CALL debug_message( debug_string, 'start' )
     4635    ENDIF
    46024636!
    46034637!-- Set Dirichlet boundary conditions for horizontal velocity components
     
    47864820       ENDIF
    47874821    ENDIF   
     4822!
     4823!-- Debug location message
     4824    IF ( debug_output )  THEN
     4825       WRITE( debug_string, * ) 'pmci_boundary_conds'
     4826       CALL debug_message( debug_string, 'end' )
     4827    ENDIF
    47884828
    47894829 END SUBROUTINE pmci_boundary_conds
Note: See TracChangeset for help on using the changeset viewer.