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

restructure/add location/debug messages

File:
1 edited

Legend:

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

    r3881 r3885  
    2525! -----------------
    2626! $Id$
     27! Changes related to global restructuring of location messages and introduction
     28! of additional debug messages
     29!
     30! 3881 2019-04-10 09:31:22Z suehring
    2731! Bugfix in level 3 initialization of pavement albedo type and pavement
    2832! emissivity
     
    544548
    545549    USE control_parameters,                                                    &
    546         ONLY:  cloud_droplets, coupling_start_time, dt_3d,      &
     550        ONLY:  cloud_droplets, coupling_start_time,                            &
     551               debug_output, debug_string,                                     &
     552               dt_3d,                                                          &
    547553               end_time, humidity, intermediate_timestep_count,                &
    548554               initializing_actions, intermediate_timestep_count_max,          &
     
    18901896    TYPE(surf_type), POINTER  ::  surf  !< surface-date type variable
    18911897
     1898!
     1899!-- Debug location message
     1900    IF ( debug_output )  THEN
     1901       WRITE( debug_string, * ) 'lsm_energy_balance', horizontal, l
     1902       CALL debug_message( debug_string, 'start' )
     1903    ENDIF
     1904
    18921905    IF ( horizontal )  THEN
    18931906       surf              => surf_lsm_h
     
    24492462    IF ( horizontal  .AND.  .NOT. constant_roughness )  CALL calc_z0_water_surface
    24502463   
    2451    
     2464    IF ( debug_output )  THEN
     2465       WRITE( debug_string, * ) 'lsm_energy_balance', horizontal, l
     2466       CALL debug_message( debug_string, 'end' )
     2467    ENDIF
     2468
    24522469    CONTAINS
    24532470!------------------------------------------------------------------------------!
     
    26322649       REAL(wp), DIMENSION(:), ALLOCATABLE ::  pr_soil_init !< temporary array used for averaging soil profiles
    26332650
    2634        CALL location_message( 'initializing land surface model', .FALSE. )
     2651       IF ( debug_output )  CALL debug_message( 'lsm_init', 'start' )
    26352652!
    26362653!--    If no cloud physics is used, rho_surface has not been calculated before
     
    49424959       ENDDO
    49434960
    4944        CALL location_message( 'finished', .TRUE. )
     4961       IF ( debug_output )  CALL debug_message( 'lsm_init', 'end' )
    49454962
    49464963    END SUBROUTINE lsm_init
     
    52715288       TYPE(surf_type), POINTER  ::  surf  !< surface-date type variable
    52725289
     5290
     5291       IF ( debug_output )  THEN
     5292          WRITE( debug_string, * ) 'lsm_soil_model', horizontal, l, calc_soil_moisture
     5293          CALL debug_message( debug_string, 'start' )
     5294       ENDIF
     5295
    52735296       IF ( horizontal )  THEN
    52745297          surf           => surf_lsm_h
     
    55665589       ENDDO
    55675590       !$OMP END PARALLEL
     5591!
     5592!--    Debug location message
     5593       IF ( debug_output )  THEN
     5594          WRITE( debug_string, * ) 'lsm_soil_model', horizontal, l, calc_soil_moisture
     5595          CALL debug_message( debug_string, 'end' )
     5596       ENDIF
    55685597
    55695598    END SUBROUTINE lsm_soil_model
Note: See TracChangeset for help on using the changeset viewer.