Ignore:
Timestamp:
Mar 5, 2009 3:33:42 PM (15 years ago)
Author:
heinze
Message:

Output of messages replaced by message handling routine.

File:
1 edited

Legend:

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

    r226 r254  
    22
    33!------------------------------------------------------------------------------!
    4 ! Actual revisions:
     4! Current revisions:
    55! -----------------
     6! Output of messages replaced by message handling routine.
    67! ATTENTION: nnz_x undefined problem still has to be solved!!!!!!!!
    78! TEST OUTPUT (TO BE REMOVED) logging mpi2 ierr values
     
    121122!--    must be equal to the number of PEs available to the job
    122123       IF ( ( npex * npey ) /= numprocs )  THEN
    123           PRINT*, '+++ init_pegrid:'
    124           PRINT*, '    number of PEs of the prescribed topology (', npex*npey, &
    125                       ') does not match the number of PEs available to the ',  &
    126                       'job (', numprocs, ')'
    127           CALL local_stop
     124          WRITE( message_string, * ) 'number of PEs of the prescribed topology (', &
     125                                     npex*npey,') does not match & the number of ',  &
     126                                     'PEs available to the job (', numprocs, ')'
     127          CALL message( 'init_pegrid', 'PA0221', 1, 2, 0, 6, 0 )
    128128       ENDIF
    129129       pdims(1) = npex
     
    134134!--    If the processor topology is prescribed by the user, the number of
    135135!--    PEs must be given in both directions
    136        PRINT*, '+++ init_pegrid:'
    137        PRINT*, '    if the processor topology is prescribed by the user, ',   &
    138                     'both values of "npex" and "npey" must be given in the ', &
    139                     'NAMELIST-parameter file'
    140        CALL local_stop
     136       message_string = 'if the processor topology is prescribed by the user, ' // &
     137                    '& both values of "npex" and "npey" must be given in the ' //    &
     138                    '&NAMELIST-parameter file'
     139       CALL message( 'init_pegrid', 'PA0222', 1, 2, 0, 6, 0 )
    141140
    142141    ENDIF
     
    145144!-- The hybrid solver can only be used in case of a 1d-decomposition along x
    146145    IF ( pdims(2) /= 1  .AND.  psolver == 'poisfft_hybrid' )  THEN
    147        IF ( myid == 0 )  THEN
    148           PRINT*, '*** init_pegrid: psolver = "poisfft_hybrid" can only be'
    149           PRINT*, '                 used in case of a 1d-decomposition along x'
    150        ENDIF
     146       message_string = 'psolver = "poisfft_hybrid" can only be' // &
     147                        '& used in case of a 1d-decomposition along x'
     148       CALL message( 'init_pegrid', 'PA0223', 1, 2, 0, 6, 0 )
    151149    ENDIF
    152150
     
    224222
    225223       IF ( .NOT. found )  THEN
    226           IF ( myid == 0 )  THEN
    227              PRINT*,'+++ init_pegrid: no matching grid for transpositions found'
    228           ENDIF
    229           CALL local_stop
     224          message_string = 'no matching grid for transpositions found'
     225          CALL message( 'init_pegrid', 'PA0224', 1, 2, 0, 6, 0 )
    230226       ENDIF
    231227
     
    239235
    240236    IF ( MOD( nxa+1 , pdims(1) ) /= 0 )  THEN
    241        IF ( myid == 0 )  THEN
    242           PRINT*,'+++ x-direction:  gridpoint number (',nx+1,') is not an'
    243           PRINT*,'                  integral divisor of the number of proces', &
    244                                    &'sors (', pdims(1),')'
    245        ENDIF
    246        CALL local_stop
     237       WRITE( message_string, * ) 'x-direction: gridpoint number (',nx+1,') is not an',&
     238                                  '& integral divisor of the number of proces', &
     239                                  'sors (', pdims(1),')'
     240       CALL message( 'init_pegrid', 'PA0225', 1, 2, 0, 6, 0 )
    247241    ELSE
    248242       nnx  = ( nxa + 1 ) / pdims(1)
    249243       IF ( nnx*pdims(1) - ( nx + 1) > nnx )  THEN
    250           IF ( myid == 0 )  THEN
    251              PRINT*,'+++ x-direction: nx does not match the requirements ', &
    252                          'given by the number of PEs'
    253              PRINT*,'                 used'
    254              PRINT*,'    please use nx = ', nx - ( pdims(1) - ( nnx*pdims(1) &
    255                          - ( nx + 1 ) ) ), ' instead of nx =', nx
    256           ENDIF
    257           CALL local_stop
     244          WRITE( message_string, * ) 'x-direction: nx does not match the', &
     245                                     'requirements given by the number of PEs', &
     246                                     '& used',&
     247                                     '& please use nx = ', nx - ( pdims(1) - ( nnx*pdims(1) &
     248                                       - ( nx + 1 ) ) ), ' instead of nx =', nx
     249          CALL message( 'init_pegrid', 'PA0226', 1, 2, 0, 6, 0 )
    258250       ENDIF
    259251    ENDIF   
     
    270262!-- Calculate array bounds in y-direction for every PE.
    271263    IF ( MOD( nya+1 , pdims(2) ) /= 0 )  THEN
    272        IF ( myid == 0 )  THEN
    273           PRINT*,'+++ y-direction:  gridpoint number (',ny+1,') is not an'
    274           PRINT*,'                  integral divisor of the number of proces', &
    275                                    &'sors (', pdims(2),')'
    276        ENDIF
    277        CALL local_stop
     264       WRITE( message_string, * ) 'y-direction: gridpoint number (',ny+1,') is not an', &
     265                                  '& integral divisor of the number of proces', &
     266                                  'sors (', pdims(2),')'
     267       CALL message( 'init_pegrid', 'PA0227', 1, 2, 0, 6, 0 )
    278268    ELSE
    279269       nny  = ( nya + 1 ) / pdims(2)
    280270       IF ( nny*pdims(2) - ( ny + 1) > nny )  THEN
    281           IF ( myid == 0 )  THEN
    282              PRINT*,'+++ x-direction: nx does not match the requirements ', &
    283                          'given by the number of PEs'
    284              PRINT*,'                 used'
    285              PRINT*,'    please use nx = ', nx - ( pdims(1) - ( nnx*pdims(1) &
    286                          - ( nx + 1 ) ) ), ' instead of nx =', nx
    287           ENDIF
    288           CALL local_stop
     271          WRITE( message_string, * ) 'y-direction: ny does not match the',&
     272                                     'requirements given by the number of PEs', &
     273                                     '& used', &
     274                                     '& please use ny = ', ny - ( pdims(2) - ( nnx*pdims(2) &
     275                                     - ( ny + 1 ) ) ), ' instead of ny =', ny
     276          CALL message( 'init_pegrid', 'PA0228', 1, 2, 0, 6, 0 )
    289277       ENDIF
    290278    ENDIF   
     
    326314       IF ( pdims(2) == 1  .AND. ( momentum_advec == 'ups-scheme'  .OR. &
    327315            scalar_advec == 'ups-scheme' ) )  THEN
    328           IF ( myid == 0 )  THEN
    329              PRINT*,'+++ WARNING: init_pegrid: 1d-decomposition along x ', &
    330                                 &'chosen but nz restrictions may occur'
    331              PRINT*,'             since ups-scheme is activated'
    332           ENDIF
     316          message_string = '1d-decomposition along x ' // &
     317                           'chosen but nz restrictions may occur' // &
     318                           '& since ups-scheme is activated'
     319          CALL message( 'init_pegrid', 'PA0229', 0, 1, 0, 6, 0 )
    333320       ENDIF
    334321       nys_x  = nys
     
    337324       nny_x  = nny
    338325       IF ( MOD( nza , pdims(1) ) /= 0 )  THEN
    339           IF ( myid == 0 )  THEN
    340              PRINT*,'+++ transposition z --> x:'
    341              PRINT*,'    nz=',nz,' is not an integral divisior of pdims(1)=', &
    342                     &pdims(1)
    343           ENDIF
    344           CALL local_stop
     326          WRITE( message_string, * ) 'transposition z --> x:', &
     327                                     '&nz=',nz,' is not an integral divisior of pdims(1)=', &
     328                                     pdims(1)
     329          CALL message( 'init_pegrid', 'PA0230', 1, 2, 0, 6, 0 )
    345330       ENDIF
    346331       nnz_x  = nza / pdims(1)
     
    371356    nzt_y  = nzt_x
    372357    IF ( MOD( nxa+1 , pdims(2) ) /= 0 )  THEN
    373        IF ( myid == 0 )  THEN
    374           PRINT*,'+++ transposition x --> y:'
    375           PRINT*,'    nx+1=',nx+1,' is not an integral divisor of ',&
    376                  &'pdims(2)=',pdims(2)
    377        ENDIF
    378        CALL local_stop
     358       WRITE( message_string, * ) 'transposition x --> y:', &
     359                                  '&nx+1=',nx+1,' is not an integral divisor of ',&
     360                                  'pdims(2)=',pdims(2)
     361       CALL message( 'init_pegrid', 'PA0231', 1, 2, 0, 6, 0 )
    379362    ENDIF
    380363    nnx_y = (nxa+1) / pdims(2)
     
    399382       nxr_z  = nxr_y
    400383       IF ( MOD( nya+1 , pdims(1) ) /= 0 )  THEN
    401           IF ( myid == 0 )  THEN
    402              PRINT*,'+++ Transposition y --> z:'
    403              PRINT*,'    ny+1=',ny+1,' is not an integral divisor of ',&
    404                     &'pdims(1)=',pdims(1)
    405           ENDIF
    406           CALL local_stop
     384          WRITE( message_string, * ) 'transposition y --> z:', &
     385                                     '& ny+1=',ny+1,' is not an integral divisor of ',&
     386                                     'pdims(1)=',pdims(1)
     387          CALL message( 'init_pegrid', 'PA0232', 1, 2, 0, 6, 0 )
    407388       ENDIF
    408389       nny_z  = (nya+1) / pdims(1)
     
    417398!--    x --> y. This condition must be fulfilled for a 1D-decomposition along x
    418399       IF ( MOD( nya+1 , pdims(1) ) /= 0 )  THEN
    419           IF ( myid == 0 )  THEN
    420              PRINT*,'+++ Transposition x --> y:'
    421              PRINT*,'    ny+1=',ny+1,' is not an integral divisor of ',&
    422                     &'pdims(1)=',pdims(1)
    423           ENDIF
    424           CALL local_stop
     400          WRITE( message_string, * ) 'transposition x --> y:', &
     401                                     '& ny+1=',ny+1,' is not an integral divisor of ',&
     402                                     'pdims(1)=',pdims(1)
     403          CALL message( 'init_pegrid', 'PA0233', 1, 2, 0, 6, 0 )
    425404       ENDIF
    426405
     
    431410    IF ( dt_dosp /= 9999999.9 )  THEN
    432411       IF ( MOD( nza, pdims(2) ) /= 0 )  THEN
    433           IF ( myid == 0 )  THEN
    434              PRINT*,'+++ Direct transposition z --> y (needed for spectra):'
    435              PRINT*,'    nz=',nz,' is not an integral divisor of ',&
    436                     &'pdims(2)=',pdims(2)
    437           ENDIF
    438           CALL local_stop
     412          WRITE( message_string, * ) 'direct transposition z --> y (needed for spectra):', &
     413                                     '& nz=',nz,' is not an integral divisor of ',&
     414                                     'pdims(2)=',pdims(2)
     415          CALL message( 'init_pegrid', 'PA0234', 1, 2, 0, 6, 0 )
    439416       ELSE
    440417          nxl_yd  = nxl
     
    609586    IF ( coupling_mode == 'atmosphere_to_ocean' )  THEN
    610587
    611        print*, '... before COMM_ACCEPT'
     588       PRINT*, '... before COMM_ACCEPT'
    612589       CALL MPI_COMM_ACCEPT( port_name, MPI_INFO_NULL, 0, MPI_COMM_WORLD, &
    613590                             comm_inter, ierr )
    614        print*, '--- ierr = ', ierr
    615        print*, '--- comm_inter atmosphere = ', comm_inter
     591       PRINT*, '--- ierr = ', ierr
     592       PRINT*, '--- comm_inter atmosphere = ', comm_inter
    616593
    617594       coupling_mode_remote = 'ocean_to_atmosphere'
     
    620597
    621598       IF ( myid == 0 )  PRINT*, '*** read: ', port_name, '  ierr = ', ierr
    622        print*, '... before COMM_CONNECT'
     599       PRINT*, '... before COMM_CONNECT'
    623600       CALL MPI_COMM_CONNECT( port_name, MPI_INFO_NULL, 0, MPI_COMM_WORLD, &
    624601                              comm_inter, ierr )
    625        print*, '--- ierr = ', ierr
    626        print*, '--- comm_inter ocean      = ', comm_inter
     602       PRINT*, '--- ierr = ', ierr
     603       PRINT*, '--- comm_inter ocean      = ', comm_inter
    627604
    628605       coupling_mode_remote = 'atmosphere_to_ocean'
     
    776753             IF ( mg_switch_to_pe0_level < mg_switch_to_pe0_level_l  .OR.  &
    777754                  mg_switch_to_pe0_level >= maximum_grid_level_l )  THEN
    778                 IF ( myid == 0 )  THEN
    779                    PRINT*, '+++ WARNING init_pegrid: mg_switch_to_pe0_level ', &
    780                                'out of range and reset to default (=0)'
    781                 ENDIF
     755                message_string = 'mg_switch_to_pe0_level ' // &
     756                                 'out of range and reset to default (=0)'
     757                CALL message( 'init_pegrid', 'PA0235', 0, 1, 0, 6, 0 )
    782758                mg_switch_to_pe0_level = 0
    783759             ELSE
     
    836812
    837813             IF ( gathered_size > subdomain_size )  THEN
    838                 IF ( myid == 0 )  THEN
    839                    PRINT*, '+++ init_pegrid: not enough memory for storing ', &
    840                                'gathered multigrid data on PE0'
    841                 ENDIF
    842                 CALL local_stop
     814                message_string = 'not enough memory for storing ' // &
     815                                 'gathered multigrid data on PE0'
     816                CALL message( 'init_pegrid', 'PA0236', 1, 2, 0, 6, 0 )
    843817             ENDIF
    844818#else
    845              PRINT*, '+++ init_pegrid: multigrid gather/scatter impossible ', &
     819             message_string = 'multigrid gather/scatter impossible ' // &
    846820                          'in non parallel mode'
    847              CALL local_stop
     821             CALL message( 'init_pegrid', 'PA0237', 1, 2, 0, 6, 0 )
    848822#endif
    849823          ENDIF
     
    10621036
    10631037              CASE DEFAULT
    1064                  IF ( myid == 0 )  PRINT*, '+++ init_pegrid: more than 10 ', &
    1065                                            ' multigrid levels'
    1066                  CALL local_stop
     1038                 message_string = 'more than 10 multigrid levels'
     1039                 CALL message( 'init_pegrid', 'PA0238', 1, 2, 0, 6, 0 )
    10671040
    10681041          END SELECT
Note: See TracChangeset for help on using the changeset viewer.