slave_meshpartition.F [SRC] [CPP] [JOB] [SCAN]
SOURCES / MAIN / SLAVE



   1 | include(dom.inc)
   2 |       SUBROUTINE slave_meshpartition(i_buffer, i_buffersize)
   3 | 
   4 | !       ================================================================!
   5 | !                                                                       !
   6 | !       slave_meshpartition.F : Fills global partition parameters for   !
   7 | !                           the slave processor.                        !
   8 | !                                                                       !
   9 | !       out             : Mesh partition parameters for slave proc.     !
  10 | !                                                                       !
  11 | !       author          : D. Poitou (Sept2011)                          !
  12 | !                                                                       !
  13 | !       ================================================================!
  14 | 
  15 | !       only for print debugging:
  16 |        USE mod_pmm
  17 | 
  18 |         USE mod_slave
  19 |         USE mod_inout
  20 |         USE mod_ftn_c
  21 | 
  22 |         IMPLICIT NONE
  23 | 
  24 |         INCLUDE 'pmm_constants.h'
  25 |         INCLUDE 'dom_constants.h'
  26 | 
  27 | !       IN
  28 |         DOM_INT          :: i_buffersize
  29 |         DOM_INT,           DIMENSION(i_buffersize) :: i_buffer
  30 | 
  31 | !       LOCAL
  32 |         DOM_INT          :: i, icell, k, ibface, iface
  33 | 
  34 | !       print*, " (",pmm_rank,") Received partition: "
  35 | !       print*, " (",pmm_rank,")          ", i_buffer
  36 | 
  37 |         IF (ALLOCATED(is_cnodes))   DEALLOCATE(is_cnodes)
  38 |         IF (ALLOCATED(is_cnnode))   DEALLOCATE(is_cnnode)
  39 |         IF (ALLOCATED(is_bface_nnode)) DEALLOCATE(is_bface_nnode)
  40 |         IF (ALLOCATED(is_bface_nodes)) DEALLOCATE(is_bface_nodes)
  41 |         IF (ALLOCATED(is_golo_cells))  DEALLOCATE(is_golo_cells)
  42 |         IF (ALLOCATED(is_golo_nodes))  DEALLOCATE(is_golo_nodes)
  43 |         IF (ALLOCATED(ts_virtbound))   DEALLOCATE(ts_virtbound)
  44 | 
  45 |         ALLOCATE(is_cnodes  (is_ncells))
  46 |         ALLOCATE(is_cnnode  (MAX_NNODES_CELL,is_ncells))
  47 |         ALLOCATE(is_bface_nnode(is_nbfaces))
  48 |         ALLOCATE(is_bface_nodes(MAX_NNODES_CELL,is_nbfaces))
  49 |         ALLOCATE(is_golo_cells(is_ntot_cells))
  50 |         ALLOCATE(is_golo_nodes(is_ntot_nodes))
  51 |         ALLOCATE(is_logo_cells(is_ncells))
  52 |         ALLOCATE(ts_virtbound(is_ntot_vfaces))
  53 | 
  54 |         i = 1
  55 | 
  56 |         DO icell = 1, is_ncells
  57 | 
  58 |           is_logo_cells(icell) = i_buffer(i)
  59 |           i = i + 1
  60 | 
  61 |           is_cnodes(icell) = i_buffer(i)
  62 |           i = i + 1
  63 |           DO k = 1, is_cnodes(icell)
  64 |             is_cnnode(k,icell) = i_buffer(i)
  65 |             i = i + 1
  66 |           ENDDO
  67 | 
  68 |         ENDDO
  69 | 
  70 |         DO ibface = 1, is_nbfaces
  71 |           is_bface_nnode(ibface) = i_buffer(i)
  72 |           i = i + 1
  73 |           DO k = 1, is_bface_nnode(ibface)
  74 |             is_bface_nodes(k,ibface) = i_buffer(i)
  75 |             i = i + 1
  76 |           ENDDO
  77 |         ENDDO
  78 | 
  79 |         is_golo_cells(1:is_ntot_cells) = i_buffer(i:i+is_ntot_cells-1)
  80 |         i = i + is_ntot_cells
  81 | 
  82 |         is_golo_nodes(1:is_ntot_nodes) = i_buffer(i:i+is_ntot_nodes-1)
  83 |         i = i + is_ntot_nodes
  84 | 
  85 |         DO iface=1, is_ntot_vfaces
  86 |           ts_virtbound(iface)%icell = i_buffer(i)
  87 |           i = i + 1
  88 |         ENDDO
  89 | 
  90 |         ts_virtbound(1:is_ntot_vfaces)%iface = i_buffer(i:i+is_ntot_vfaces-1)
  91 |         i = i + is_ntot_vfaces
  92 | 
  93 |         DO iface=1, is_ntot_vfaces
  94 |           ts_virtbound(iface)%icell_next = i_buffer(i)
  95 |           i = i + 1
  96 |         ENDDO
  97 | 
  98 |         ts_virtbound(1:is_ntot_vfaces)%iface_next = i_buffer(i:i+is_ntot_vfaces-1)
  99 |         i = i + is_ntot_vfaces
 100 | 
 101 | !       PRINT*,"rank",pmm_rank, i-1,"/", i_buffersize
 102 | 
 103 |       END SUBROUTINE slave_meshpartition


slave_meshpartition.F could be called by:
Makefile [SOURCES] - 148
pmm_sendpartition.F [SOURCES/MAIN] - 48
slave_receive.F [SOURCES/MAIN/SLAVE] - 57