meshpartition.F [SRC] [CPP] [JOB] [SCAN]
SOURCES / MAIN / MASTER



   1 | include(dom.inc)
   2 | 
   3 |       SUBROUTINE meshpartition
   4 | !     ================================================================!
   5 | !                                                                     !
   6 | !     meshpartition.F : Controls the partitioning of the mesh and the !
   7 | !                       redistribution of the connectivities.         !
   8 | !     out            :                                                !
   9 | !                                                                     !
  10 | !     author         : D. Poitou (sept2011)                           !
  11 | !                                                                     !
  12 | !     ================================================================!
  13 | 
  14 |       USE mod_pmm
  15 |       USE mod_prissma
  16 |       USE mod_inout
  17 | 
  18 |       IMPLICIT NONE
  19 | 
  20 |       include 'pmm_constants.h'
  21 |       include 'dom_constants.h'
  22 | 
  23 | !     LOCAL
  24 |       DOM_INT  :: icell, inode, iface, ibnd, ilocal, nbnodes
  25 |       DOM_INT  :: i, j, k, dummy, next_cell, next_face, next_local
  26 |       DOM_INT  :: ivface
  27 |       DOM_INT  :: MAX_CELL_PART
  28 |       DOM_REAL :: weight
  29 |       CHARACTER*80 :: file, file2
  30 | 
  31 |       DOM_REAL, allocatable, dimension(:)   :: relwork
  32 |       DOM_REAL, allocatable, dimension(:,:) :: x_cells
  33 |       DOM_INT , allocatable, dimension(:)   :: ielogo
  34 | 
  35 |       DOM_INT , allocatable, dimension(:)   :: cnodes, cfaces
  36 |       DOM_INT , allocatable, dimension(:,:) :: cnnode, cnface
  37 |       LOGICAL , allocatable, dimension(:,:) :: node_part
  38 |       DOM_INT , allocatable, dimension(:,:) :: face_part
  39 |       DOM_INT , allocatable, dimension(:,:) :: facenodes
  40 |       DOM_INT , allocatable, dimension(:)   :: nfcelt
  41 |       DOM_INT , allocatable, dimension(:,:) :: neighs
  42 | 
  43 | !     EXTERNAL
  44 |       external heap_sort
  45 | 
  46 |       PRINT*,"      Original Mesh:"
  47 |       PRINT*,"      - Ncells :", i_dom_ncells
  48 |       PRINT*,"      - Nnodes :", i_dom_nnodes
  49 |       PRINT*,"      - Nbfaces:", i_dom_nbfaces
  50 |       PRINT*,"  >>> Mesh partitionning over", i_dom_npart, "domains"
  51 |       PRINT*
  52 | 
  53 | !     --------------------------------------!
  54 | !     Calculate graph partitionig using RCB !
  55 | !     --------------------------------------!
  56 | 
  57 | !     Lire les coordonnées des cellules -> x_cells
  58 | 
  59 |       file   = path(1:len_trim(path))//'/Centercells.in'
  60 |       OPEN(FILE_CELLS , FILE=file  , FORM='UNFORMATTED')
  61 | 
  62 |       ALLOCATE(x_cells (i_dom_ndim, i_dom_ncells))
  63 | 
  64 |       DO icell = 1, i_dom_ncells
  65 |         READ(FILE_CELLS) dummy, (x_cells(j,icell), j=1,i_dom_ndim)
  66 |       ENDDO
  67 | 
  68 |       CLOSE(FILE_CELLS)
  69 | 
  70 |       weight = -1.0
  71 | 
  72 |       ALLOCATE(ielogo   (i_dom_ncells))
  73 |       ALLOCATE(relwork  (i_dom_ncells))
  74 |       ALLOCATE(ip_beg   (i_dom_npart))
  75 |       ALLOCATE(ip_len   (i_dom_npart))
  76 |       ALLOCATE(ip_partition(i_dom_ncells))
  77 | 
  78 |       CALL rcb(i_dom_ndim, i_dom_ncells, i_dom_npart, x_cells, weight,  &
  79 |      &    heap_sort, relwork, ip_partition, ielogo, ip_beg, ip_len)
  80 | 
  81 |       MAX_CELL_PART = MAXVAL(ip_len)
  82 | 
  83 |       DEALLOCATE(x_cells)
  84 |       DEALLOCATE(relwork)
  85 |       DEALLOCATE(ielogo)
  86 | 
  87 | !     -----------------------------------------!
  88 | !     Distribute the vectors on the subdomains !
  89 | !     -----------------------------------------!
  90 | 
  91 |       file  = path(1:len_trim(path))//'/Cellnodes.in'
  92 |       file2 = path(1:len_trim(path))//'/Cell2faces.in'
  93 | 
  94 |       OPEN(FILE_CLNOD, FILE=file , FORM='UNFORMATTED')
  95 |       OPEN(FILE_CFACE, FILE=file2, FORM='UNFORMATTED')
  96 | 
  97 |       ALLOCATE(cnodes(i_dom_ncells))
  98 |       ALLOCATE(cfaces(i_dom_ncells))
  99 |       ALLOCATE(cnnode(MAX_NNODES_CELL,i_dom_ncells))
 100 |       ALLOCATE(cnface(MAX_NFACES_CELL,i_dom_ncells))
 101 | 
 102 |       DO icell=1,i_dom_ncells
 103 |         READ(FILE_CLNOD) dummy, cnodes(icell),                          &
 104 |      &                  (cnnode(j,icell),j=1,cnodes(icell))
 105 | 
 106 |         READ(FILE_CFACE) dummy, cfaces(icell),                          &
 107 |      &                  (cnface(j,icell),j=1,cfaces(icell))
 108 | 
 109 |       ENDDO
 110 | 
 111 |       CLOSE(FILE_CLNOD)
 112 |       CLOSE(FILE_CFACE)
 113 | 
 114 |       ALLOCATE(node_part(i_dom_nnodes,i_dom_npart))
 115 |       ALLOCATE(face_part(i_dom_nfaces,i_dom_npart))
 116 |       ALLOCATE(ip_golo_cells(i_dom_ncells,i_dom_npart))
 117 | 
 118 |       ip_golo_cells = 0
 119 |       node_part = .false.
 120 |       face_part = 0
 121 | 
 122 |       DO i = 1, i_dom_npart
 123 |         DO j = 1, ip_len(i)
 124 | 
 125 |           icell = ip_partition(j+ip_beg(i)-1)
 126 |           ip_golo_cells(icell,i) = j
 127 | 
 128 | !         --------------------------!
 129 | !         Detect nodes in subdomain !
 130 | !         --------------------------!
 131 |           DO k=1, cnodes(icell)
 132 |             node_part(cnnode(k,icell),i) = .true.
 133 |           ENDDO
 134 | 
 135 | !         --------------------------!
 136 | !         Detect faces in subdomain !
 137 | !         --------------------------!
 138 |           DO k=1, cfaces(icell)
 139 |             face_part(cnface(k,icell),i) = 1
 140 |           ENDDO
 141 |         ENDDO
 142 | 
 143 |       ENDDO
 144 | 
 145 |       DEALLOCATE(cfaces)
 146 | 
 147 | !     --------------------------------------------------!
 148 | !     Create connections between local and global nodes !
 149 | !     --------------------------------------------------!
 150 | 
 151 |       ALLOCATE(ip_nnodes(i_dom_npart))
 152 |       ALLOCATE(ip_logo_nodes(MAX_CELL_PART*MAX_NNODES_CELL,i_dom_npart))
 153 |       ALLOCATE(ip_golo_nodes(i_dom_nnodes,i_dom_npart))
 154 | 
 155 |       ip_nnodes     = 0
 156 |       ip_logo_nodes = 0
 157 |       ip_golo_nodes = 0
 158 | 
 159 |       DO inode= 1,i_dom_nnodes
 160 |         DO i = 1, i_dom_npart
 161 | 
 162 |           IF(node_part(inode,i)) THEN
 163 | !           PRINT*,inode,"is in part", i
 164 |             ip_nnodes(i) = ip_nnodes(i) + 1
 165 |             k            = ip_nnodes(i)
 166 |             ip_logo_nodes(k,i)     = inode
 167 |             ip_golo_nodes(inode,i) = k
 168 |           ENDIF
 169 | 
 170 |         ENDDO
 171 |       ENDDO
 172 | !     PRINT*, ip_nnodes(:), sum(ip_nnodes)
 173 | 
 174 |       DEALLOCATE(node_part)
 175 | 
 176 | !     -----------------------!
 177 | !     Count faces in domains !
 178 | !     -----------------------!
 179 | 
 180 |       ALLOCATE(ip_nfaces(i_dom_npart))
 181 |       ip_nfaces = 0
 182 | 
 183 |       DO i = 1, i_dom_npart
 184 |         ip_nfaces(i) = SUM(face_part(:,i))
 185 |       ENDDO
 186 | !     PRINT*, ip_nfaces(:), SUM(ip_nfaces)
 187 | 
 188 |       i_dom_nvfaces = 0
 189 |       DO iface = 1, i_dom_nfaces
 190 |         IF(SUM(face_part(iface,:)).eq.2) i_dom_nvfaces = i_dom_nvfaces + 2
 191 |       ENDDO
 192 | 
 193 | !     -----------------------------------------------------------!
 194 | !     Create connections between local and global boundary faces !
 195 | !     -----------------------------------------------------------!
 196 | 
 197 |       ALLOCATE(facenodes(MAX_NFACES_CELL+1, i_dom_nfaces))
 198 |       facenodes = 0
 199 | 
 200 |       file = path(1:len_trim(path))//'/Facelist.in'
 201 |       OPEN(FILE_FC ,FILE=file,FORM='UNFORMATTED')
 202 | 
 203 |       DO i=1, i_dom_nfaces
 204 |         READ(FILE_FC) dummy, nbnodes,                                   &
 205 |      &                    (facenodes(j,i),j=2,nbnodes+1)
 206 |         facenodes(1,i) = nbnodes
 207 |       ENDDO
 208 |       CLOSE(FILE_FC)
 209 | 
 210 |       ALLOCATE(ip_bface_nnode(i_dom_nbfaces,i_dom_npart))
 211 |       ALLOCATE(ip_bface_nodes(MAX_NNODES_CELL,i_dom_nbfaces,i_dom_npart))
 212 |       ip_bface_nnode = 0
 213 |       ip_bface_nodes = 0
 214 | 
 215 |       ALLOCATE(ip_nbfaces(i_dom_npart))
 216 |       ALLOCATE(ip_logo_bfaces(i_dom_nbfaces*i_dom_npart,i_dom_npart))
 217 |       ip_nbfaces     = 0
 218 |       ip_logo_bfaces = 0
 219 | 
 220 |       file = path(1:len_trim(path))//'/CLdata.in'
 221 |       OPEN(FILE_CLDAT, FILE=file , FORM='UNFORMATTED')
 222 | 
 223 |       DO ibnd = 1, i_dom_nbfaces
 224 | 
 225 |         READ(FILE_CLDAT) icell, iface
 226 |         iface = cnface(iface,icell)
 227 | 
 228 |         DO i = 1, i_dom_npart
 229 | 
 230 |           IF(face_part(iface,i).eq.1 ) THEN
 231 | !         print*, " Bndface",ibnd, i_bface,"is in part",i
 232 | 
 233 |             ip_nbfaces(i) = ip_nbfaces(i) + 1
 234 |             k              = ip_nbfaces(i)
 235 | 
 236 |             ! Connectivity face-node at boundary for gather_face
 237 |             ip_bface_nnode(k,i) = facenodes(1,iface)
 238 |             DO inode = 1, facenodes(1,iface)
 239 |               ilocal = ip_golo_nodes(facenodes(inode+1,iface),i)
 240 |               ip_bface_nodes(inode,k,i) = ilocal
 241 |             ENDDO
 242 |             ip_logo_bfaces(k,i) = ibnd
 243 |           ENDIF
 244 | 
 245 |         ENDDO
 246 |       ENDDO
 247 | !     PRINT*, ip_nbfaces(:), SUM(ip_nbfaces)
 248 | 
 249 |       CLOSE(FILE_CLDAT)
 250 | 
 251 |       DEALLOCATE(face_part)
 252 |       DEALLOCATE(cnface)
 253 |       DEALLOCATE(facenodes)
 254 | 
 255 | !     -------------------------------------------------------!
 256 | !     Reconstruction of local connectivities and             !
 257 | !     create virtual faces on boundaries between subdomains  !
 258 | !     -------------------------------------------------------!
 259 | 
 260 |       ALLOCATE(nfcelt  (i_dom_ncells))
 261 |       ALLOCATE(neighs  (2*MAX_NFACES_CELL,i_dom_ncells))
 262 | 
 263 |       file    = path(1:len_trim(path))//'/Cell2cells.in'
 264 |       OPEN(FILE_C2C, FILE=file, FORM='UNFORMATTED')
 265 | 
 266 |       DO icell=1, i_dom_ncells
 267 |         READ(FILE_C2C) dummy, nfcelt(icell),                            &
 268 |      &                (neighs(j,icell),j=1,(2*nfcelt(icell)))
 269 | 
 270 |       ENDDO
 271 | 
 272 |       CLOSE(FILE_C2C)
 273 | 
 274 |       ALLOCATE(ip_cnodes(MAX_CELL_PART,i_dom_npart))
 275 |       ALLOCATE(ip_cnnode(MAX_NNODES_CELL,MAX_CELL_PART,i_dom_npart))
 276 |       ip_cnodes = 0
 277 |       ip_cnnode = 0
 278 | 
 279 |       ALLOCATE(ip_nvfaces(i_dom_npart))
 280 |       ALLOCATE(i_vface(4,i_dom_nvfaces))
 281 |       ip_nvfaces = 0
 282 |       i_vface    = 0
 283 |       ivface     = 0
 284 | 
 285 |       DO i = 1, i_dom_npart
 286 |         DO j = 1, ip_len(i)
 287 | 
 288 |           icell = ip_partition(j+ip_beg(i)-1)
 289 | !         -------------------------------------------------------------------!
 290 | !         Copy node connectivity for each part with local number of the node !
 291 | !         -------------------------------------------------------------------!
 292 |           ip_cnodes(j,i)   = cnodes(icell)
 293 | 
 294 |           DO k=1, cnodes(icell)
 295 |             inode  =  cnnode(k,icell)
 296 |             ilocal = ip_golo_nodes(inode,i)
 297 |             ip_cnnode(k,j,i) = ilocal
 298 |           ENDDO
 299 | 
 300 | !         --------------------!
 301 | !         Count virtual faces !
 302 | !         --------------------!
 303 | 
 304 |           DO iface=1, nfcelt(icell)
 305 |             next_cell = neighs(2*iface-1,icell)
 306 |             next_face = neighs(2*iface  ,icell)
 307 | 
 308 |             IF (next_cell.ne.0) THEN
 309 |               next_local = ip_golo_cells(next_cell,i)
 310 | 
 311 |               IF(next_local.eq.0) THEN
 312 |                 ivface        = ivface + 1 
 313 |                 ip_nvfaces(i) = ip_nvfaces(i) + 1
 314 | 
 315 |                 i_vface(1,ivface) = icell
 316 |                 i_vface(2,ivface) = iface
 317 |                 i_vface(3,ivface) = next_cell
 318 |                 i_vface(4,ivface) = next_face
 319 | 
 320 |               ENDIF
 321 |             ENDIF
 322 | 
 323 |           ENDDO
 324 | 
 325 |         ENDDO
 326 |       ENDDO
 327 | 
 328 |       DEALLOCATE(cnodes)
 329 |       DEALLOCATE(cnnode)
 330 |       DEALLOCATE(nfcelt)
 331 |       DEALLOCATE(neighs)
 332 | 
 333 |       END SUBROUTINE meshpartition


meshpartition.F could be called by:
Makefile [SOURCES] - 145
master_control.F [SOURCES/MAIN/MASTER] - 58