Ignore:
Timestamp:
Nov 7, 2011 2:18:25 PM (12 years ago)
Author:
fricke
Message:

Modifications of the multigrid pressure solver

File:
1 edited

Legend:

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

    r760 r778  
    44! Current revisions:
    55! -----------------
    6 !
     6! Calculation of subdomain_size now considers the number of ghost points.
     7! Further coarsening on PE0 is now possible for multigrid solver if the
     8! collected field has more grid points than the subdomain of an PE.
    79!
    810! ATTENTION: nnz_x undefined problem still has to be solved!!!!!!!!
     
    114116    IMPLICIT NONE
    115117
    116     INTEGER ::  gathered_size, i, id_inflow_l, id_recycling_l, ind(5), j, k, &
     118    INTEGER ::  i, id_inflow_l, id_recycling_l, ind(5), j, k,                &
    117119                maximum_grid_level_l, mg_switch_to_pe0_level_l, mg_levels_x, &
    118120                mg_levels_y, mg_levels_z, nnx_y, nnx_z, nny_x, nny_z, nnz_x, &
    119121                nnz_y, numproc_sqr, nx_total, nxl_l, nxr_l, nyn_l, nys_l,    &
    120                 nzb_l, nzt_l, omp_get_num_threads, subdomain_size
     122                nzb_l, nzt_l, omp_get_num_threads
    121123
    122124    INTEGER, DIMENSION(:), ALLOCATABLE ::  ind_all, nxlf, nxrf, nynf, nysf
     
    879881
    880882          ELSE
    881 
    882883             mg_switch_to_pe0_level_l = 0
    883884             maximum_grid_level_l = maximum_grid_level
     
    889890!--       by user
    890891          IF ( mg_switch_to_pe0_level == 0 )  THEN
    891 
    892892             IF ( mg_switch_to_pe0_level_l /= 0 )  THEN
    893893                mg_switch_to_pe0_level = mg_switch_to_pe0_level_l
     
    922922
    923923       grid_level_count = 0
     924
    924925       nxl_l = nxl; nxr_l = nxr; nys_l = nys; nyn_l = nyn; nzt_l = nzt
    925926
     
    952953!--          The size of this gathered array must not be larger than the
    953954!--          array tend, which is used in the multigrid scheme as a temporary
    954 !--          array
    955              subdomain_size = ( nxr - nxl + 3 )     * ( nyn - nys + 3 )     * &
    956                               ( nzt - nzb + 2 )
     955!--          array. Therefore the subdomain size of an PE is calculated and
     956!--          the size of the gathered grid. These values are used in 
     957!--          routines pres and poismg
     958             subdomain_size = ( nxr - nxl + 2 * nbgp + 1 ) * &
     959                              ( nyn - nys + 2 * nbgp + 1 ) * ( nzt - nzb + 2 )
    957960             gathered_size  = ( nxr_l - nxl_l + 3 ) * ( nyn_l - nys_l + 3 ) * &
    958961                              ( nzt_l - nzb + 2 )
    959962
    960              IF ( gathered_size > subdomain_size )  THEN
    961                 message_string = 'not enough memory for storing ' // &
    962                                  'gathered multigrid data on PE0'
    963                 CALL message( 'init_pegrid', 'PA0236', 1, 2, 0, 6, 0 )
    964              ENDIF
    965963#else
    966964             message_string = 'multigrid gather/scatter impossible ' // &
     
    981979          nyn_l = nyn_l / 2
    982980          nzt_l = nzt_l / 2
     981
    983982       ENDDO
    984983
     
    987986       maximum_grid_level = 0
    988987
     988    ENDIF
     989
     990!-- Temporary problem: In the moment the summation to calculate maxerror
     991!-- in routine poismg crashes the program if the first coarsement is on PE0.
     992!-- Further work required.
     993    IF ( maximum_grid_level == mg_switch_to_pe0_level )  THEN
     994       message_string = 'At least one coarser grid must be calculated ' // &
     995                        'on the subdomain of each PE'
     996       CALL message( 'poismg', 'PA0236', 1, 2, 0, 6, 0 )
    989997    ENDIF
    990998
Note: See TracChangeset for help on using the changeset viewer.