Ignore:
Timestamp:
May 28, 2018 7:55:41 AM (6 years ago)
Author:
Giersch
Message:

Code adjusted according to coding standards, renamed namelists, error messages revised until PA0347, output CASE 108 disabled

File:
1 edited

Legend:

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

    r2938 r3045  
    2525! -----------------
    2626! $Id$
     27! Error messages revised
     28!
     29! 2938 2018-03-27 15:52:42Z suehring
    2730! - No checks for domain decomposition in case of turbulence generator
    2831!  (is done in stg module)
     
    341344!--    must be equal to the number of PEs available to the job
    342345       IF ( ( npex * npey ) /= numprocs )  THEN
    343           WRITE( message_string, * ) 'number of PEs of the prescribed ',   &
    344               'topology (', npex*npey,') does not match & the number of ', &
     346          WRITE( message_string, * ) 'number of PEs of the prescribed ',       &
     347              'topology (', npex*npey,') does not match the number of ',      &
    345348              'PEs available to the job (', numprocs, ')'
    346349          CALL message( 'init_pegrid', 'PA0221', 1, 2, 0, 6, 0 )
     
    353356!--    If the processor topology is prescribed by the user, the number of
    354357!--    PEs must be given in both directions
    355        message_string = 'if the processor topology is prescribed by th' //  &
    356                 'e user& both values of "npex" and "npey" must be given' // &
     358       message_string = 'if the processor topology is prescribed by th' //     &
     359                'e user both values of "npex" and "npey" must be given' //    &
    357360                ' in the &NAMELIST-parameter file'
    358361       CALL message( 'init_pegrid', 'PA0222', 1, 2, 0, 6, 0 )
     
    450453!
    451454!-- Calculate array bounds along x-direction for every PE.
    452     ALLOCATE( nxlf(0:pdims(1)-1), nxrf(0:pdims(1)-1), nynf(0:pdims(2)-1), &
     455    ALLOCATE( nxlf(0:pdims(1)-1), nxrf(0:pdims(1)-1), nynf(0:pdims(2)-1),      &
    453456              nysf(0:pdims(2)-1) )
    454457
    455458    IF ( MOD( nx+1 , pdims(1) ) /= 0 )  THEN
    456        WRITE( message_string, * ) 'x-direction: gridpoint number (',nx+1,') ',&
    457                                'is not an& integral divisor of the number ',  &
    458                                'processors (', pdims(1),')'
     459       WRITE( message_string, * ) 'x-direction: gridpoint number (',nx+1,') ', &
     460                               'is not an integral divisor of the number ',    &
     461                               'of processors (', pdims(1),')'
    459462       CALL message( 'init_pegrid', 'PA0225', 1, 2, 0, 6, 0 )
    460463    ELSE
    461464       nnx  = ( nx + 1 ) / pdims(1)
    462        IF ( nnx*pdims(1) - ( nx + 1) > nnx )  THEN
    463           WRITE( message_string, * ) 'x-direction: nx does not match the',    &
    464                        'requirements given by the number of PEs &used',       &
    465                        '& please use nx = ', nx - ( pdims(1) - ( nnx*pdims(1) &
    466                                       - ( nx + 1 ) ) ), ' instead of nx =', nx
    467           CALL message( 'init_pegrid', 'PA0226', 1, 2, 0, 6, 0 )
    468        ENDIF
    469465    ENDIF   
    470466
     
    480476    IF ( MOD( ny+1 , pdims(2) ) /= 0 )  THEN
    481477       WRITE( message_string, * ) 'y-direction: gridpoint number (',ny+1,') ', &
    482                            'is not an& integral divisor of the number of',     &
     478                           'is not an integral divisor of the number of',      &
    483479                           'processors (', pdims(2),')'
    484480       CALL message( 'init_pegrid', 'PA0227', 1, 2, 0, 6, 0 )
    485481    ELSE
    486482       nny  = ( ny + 1 ) / pdims(2)
    487        IF ( nny*pdims(2) - ( ny + 1) > nny )  THEN
    488           WRITE( message_string, * ) 'y-direction: ny does not match the',    &
    489                        'requirements given by the number of PEs &used ',      &
    490                        '& please use ny = ', ny - ( pdims(2) - ( nnx*pdims(2) &
    491                                      - ( ny + 1 ) ) ), ' instead of ny =', ny
    492           CALL message( 'init_pegrid', 'PA0228', 1, 2, 0, 6, 0 )
    493        ENDIF
    494483    ENDIF   
    495484
     
    533522          IF ( MOD( nz , pdims(1) ) /= 0 )  THEN
    534523             WRITE( message_string, * ) 'transposition z --> x:',              &
    535                        '&nz=',nz,' is not an integral divisior of pdims(1)=',  &
     524                       ' nz=',nz,' is not an integral divisior of pdims(1)=',  &
    536525                                                                   pdims(1)
    537526             CALL message( 'init_pegrid', 'PA0230', 1, 2, 0, 6, 0 )
     
    555544       IF ( MOD( nx+1 , pdims(2) ) /= 0 )  THEN
    556545          WRITE( message_string, * ) 'transposition x --> y:',                 &
    557                             '&nx+1=',nx+1,' is not an integral divisor of ',   &
     546                            ' nx+1=',nx+1,' is not an integral divisor of ',   &
    558547                            'pdims(2)=',pdims(2)
    559548          CALL message( 'init_pegrid', 'PA0231', 1, 2, 0, 6, 0 )
     
    584573          IF ( MOD( ny+1 , pdims(1) ) /= 0 )  THEN
    585574             WRITE( message_string, * ) 'transposition y --> z:',              &
    586                                '& ny+1=',ny+1,' is not an integral divisor of',&
     575                               ' ny+1=',ny+1,' is not an integral divisor of', &
    587576                               ' pdims(1)=',pdims(1)
    588577             CALL message( 'init_pegrid', 'PA0232', 1, 2, 0, 6, 0 )
     
    595584          IF ( MOD( ny+1 , pdims(1) ) /= 0 )  THEN
    596585             WRITE( message_string, * ) 'transposition x --> y:',              &
    597                                '& ny+1=',ny+1,' is not an integral divisor of',&
     586                               ' ny+1=',ny+1,' is not an integral divisor of', &
    598587                               ' pdims(1)=',pdims(1)
    599588             CALL message( 'init_pegrid', 'PA0233', 1, 2, 0, 6, 0 )
     
    609598       IF ( MOD( nz, pdims(2) ) /= 0 )  THEN
    610599          WRITE( message_string, * ) 'direct transposition z --> y (needed ',  &
    611                     'for spectra):& nz=',nz,' is not an integral divisor of ', &
     600                    'for spectra): nz=',nz,' is not an integral divisor of ', &
    612601                    'pdims(2)=',pdims(2)
    613602          CALL message( 'init_pegrid', 'PA0234', 1, 2, 0, 6, 0 )
     
    974963!
    975964!--          Check pre-defined value and reset to default, if neccessary
    976              IF ( mg_switch_to_pe0_level < mg_switch_to_pe0_level_l  .OR.  &
     965             IF ( mg_switch_to_pe0_level < mg_switch_to_pe0_level_l  .OR.      &
    977966                  mg_switch_to_pe0_level >= maximum_grid_level_l )  THEN
    978                 message_string = 'mg_switch_to_pe0_level ' // &
     967                message_string = 'mg_switch_to_pe0_level ' //                  &
    979968                                 'out of range and reset to 0'
    980969                CALL message( 'init_pegrid', 'PA0235', 0, 1, 0, 6, 0 )
     
    10381027             subdomain_size = ( nxr - nxl + 2 * nbgp + 1 ) * &
    10391028                              ( nyn - nys + 2 * nbgp + 1 ) * ( nzt - nzb + 2 )
    1040              gathered_size  = ( nxr_l - nxl_l + 3 ) * ( nyn_l - nys_l + 3 ) * &
     1029             gathered_size  = ( nxr_l - nxl_l + 3 ) * ( nyn_l - nys_l + 3 ) *  &
    10411030                              ( nzt_l - nzb + 2 )
    10421031
    10431032#else
    1044              message_string = 'multigrid gather/scatter impossible ' // &
     1033             message_string = 'multigrid gather/scatter impossible ' //        &
    10451034                          'in non parallel mode'
    10461035             CALL message( 'init_pegrid', 'PA0237', 1, 2, 0, 6, 0 )
     
    10631052
    10641053!
    1065 !--    Temporary problem: Currently calculation of maxerror iin routine poismg crashes
     1054!--    Temporary problem: Currently calculation of maxerror in routine poismg crashes
    10661055!--    if grid data are collected on PE0 already on the finest grid level.
    10671056!--    To be solved later.
Note: See TracChangeset for help on using the changeset viewer.