Changeset 1384 for palm


Ignore:
Timestamp:
May 2, 2014 2:31:06 PM (10 years ago)
Author:
raasch
Message:

output of location messages to stdout

Location:
palm/trunk/SOURCE
Files:
6 edited

Legend:

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

    r1366 r1384  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! location messages added
    2323!
    2424! Former revisions:
     
    260260    REAL(wp)    ::  remote = 0.0_wp                  !:
    261261    REAL(wp)    ::  simulation_time_since_reference  !:
     262
     263
     264    CALL location_message( 'checking parameters' )
    262265
    263266!
     
    36913694       CALL message( 'check_parameters', 'PA0378', 1, 2, 0, 6, 0 )
    36923695    ENDIF
     3696
     3697    CALL location_message( 'finished' )
     3698
    36933699!
    36943700!-- Check &userpar parameters
     
    36963702
    36973703
    3698 
    36993704 END SUBROUTINE check_parameters
  • palm/trunk/SOURCE/init_3d_model.f90

    r1362 r1384  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! location messages added
    2323!
    2424! Former revisions:
     
    224224
    225225
     226    CALL location_message( 'allocating arrays' )
    226227!
    227228!-- Allocate arrays
     
    592593    intermediate_timestep_count = 1  ! needed when simulated_time = 0.0
    593594       
     595    CALL location_message( 'finished' )
    594596!
    595597!-- Initialize model variables
     
    600602!--    Initial profiles of the variables must be computes.
    601603       IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
     604
     605          CALL location_message( 'initializing with 1D model profiles' )
    602606!
    603607!--       Use solutions of the 1D model as initial profiles,
     
    718722          ENDIF
    719723
     724          CALL location_message( 'finished' )
     725
    720726       ELSEIF ( INDEX(initializing_actions, 'set_constant_profiles') /= 0 ) &
    721727       THEN
    722728
     729          CALL location_message( 'initializing with constant profiles' )
    723730!
    724731!--       Overwrite initial profiles in case of nudging
     
    829836          IF ( sloping_surface )  CALL init_slope
    830837
     838          CALL location_message( 'finished' )
     839
    831840       ELSEIF ( INDEX(initializing_actions, 'by_user') /= 0 ) &
    832841       THEN
     842
     843          CALL location_message( 'initializing by user' )
    833844!
    834845!--       Initialization will completely be done by the user
    835846          CALL user_init_3d_model
    836847
    837        ENDIF
     848          CALL location_message( 'finished' )
     849
     850       ENDIF
     851
     852       CALL location_message( 'initializing statistics, boundary conditions, etc.' )
     853
    838854!
    839855!--    Bottom boundary
     
    11051121       ENDIF
    11061122       
     1123       CALL location_message( 'finished' )
    11071124
    11081125    ELSEIF ( TRIM( initializing_actions ) == 'read_restart_data'  .OR.    &
    11091126         TRIM( initializing_actions ) == 'cyclic_fill' )  &
    11101127    THEN
     1128
     1129       CALL location_message( 'initializing in case of restart / cyclic_fill' )
    11111130!
    11121131!--    When reading data for cyclic fill of 3D prerun data files, read
     
    12931312       IF ( ocean )  tsa_m = 0.0_wp
    12941313
     1314       CALL location_message( 'finished' )
     1315
    12951316    ELSE
    12961317!
     
    14621483         TRIM( initializing_actions ) /= 'cyclic_fill' )  THEN
    14631484
     1485       CALL location_message( 'creating initial disturbances' )
    14641486       CALL disturb_field( nzb_u_inner, tend, u )
    14651487       CALL disturb_field( nzb_v_inner, tend, v )
     1488       CALL location_message( 'finished' )
     1489
     1490       CALL location_message( 'calling pressure solver' )
    14661491       n_sor = nsor_ini
    14671492       !$acc data copyin( d, ddzu, ddzw, nzb_s_inner, nzb_u_inner )            &
     
    14721497       !$acc end data
    14731498       n_sor = nsor
     1499       CALL location_message( 'finished' )
     1500
    14741501    ENDIF
    14751502
     
    18441871    DEALLOCATE( ngp_2dh_l, ngp_2dh_outer_l, ngp_3d_inner_l, ngp_3d_inner_tmp )
    18451872
     1873    CALL location_message( 'leaving init_3d_model' )
    18461874
    18471875 END SUBROUTINE init_3d_model
  • palm/trunk/SOURCE/init_pegrid.f90

    r1354 r1384  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! location messages added
    2323!
    2424! Former revisions:
     
    175175#if defined( __parallel )
    176176
     177    CALL location_message( 'creating virtual PE grids + MPI derived data types' )
    177178!
    178179!-- Determine the processor topology or check it, if prescribed by the user
     
    10701071                        comm1dx, ierr )
    10711072
     1073    CALL location_message( 'finished' )
     1074
    10721075#elif ! defined ( __parallel )
    10731076    IF ( bc_lr == 'dirichlet/radiation' )  THEN
  • palm/trunk/SOURCE/message.f90

    r1321 r1384  
    2121! Current revisions:
    2222! -----------------
    23 !
     23! routine location_message added
    2424!
    2525! Former revisions:
     
    5151!------------------------------------------------------------------------------!
    5252
    53     USE control_parameters,                                                  &
     53    USE control_parameters,                                                    &
    5454        ONLY:  abort_mode, message_string
    5555
     
    206206
    207207 END SUBROUTINE message
     208
     209
     210 SUBROUTINE location_message( location )
     211
     212!------------------------------------------------------------------------------!
     213! Description:
     214! ------------
     215! Prints out the given location on stdout
     216!------------------------------------------------------------------------------!
     217
     218    USE pegrid,                                                                &
     219        ONLY :  myid
     220
     221    IMPLICIT NONE
     222
     223    CHARACTER(LEN=*) ::  location
     224
     225
     226    IF ( myid == 0 )  THEN
     227       WRITE ( 6, '(6X,''... '',A)' )  TRIM( location )
     228       CALL local_flush( 6 )
     229    ENDIF
     230
     231 END SUBROUTINE location_message
  • palm/trunk/SOURCE/parin.f90

    r1366 r1384  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! location messages added
    2323!
    2424! Former revisions:
     
    338338!-- First read values of environment variables (this NAMELIST file is
    339339!-- generated by mrun)
     340    CALL location_message( 'reading environment parameters from ENVPAR' )
    340341    OPEN ( 90, FILE='ENVPAR', STATUS='OLD', FORM='FORMATTED', ERR=30 )
    341342    READ ( 90, envpar, ERR=31, END=32 )
    342343    CLOSE ( 90 )
     344    CALL location_message( 'finished' )
    343345
    344346!
     
    363365    io_group  = MOD( myid+1, io_blocks )
    364366
     367    CALL location_message( 'reading NAMELIST parameters from PARIN' )
    365368!
    366369!-- Data is read in parallel by groups of PEs
     
    481484    ENDDO
    482485
     486    CALL location_message( 'finished' )
     487
    483488    RETURN
    484489
  • palm/trunk/SOURCE/time_integration.f90

    r1381 r1384  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! location messages added
    2323!
    2424! Former revisions:
     
    250250#endif
    251251
     252    CALL location_message( 'beginning with time-stepping' )
    252253!
    253254!-- Start of the time loop
     
    949950#endif
    950951
     952    CALL location_message( 'finished time-stepping' )
     953
    951954 END SUBROUTINE time_integration
Note: See TracChangeset for help on using the changeset viewer.