[cig-commits] r8538 - seismo/2D/SPECFEM2D/trunk

walter at geodynamics.org walter at geodynamics.org
Fri Dec 7 15:54:40 PST 2007


Author: walter
Date: 2007-12-07 15:54:39 -0800 (Fri, 07 Dec 2007)
New Revision: 8538

Modified:
   seismo/2D/SPECFEM2D/trunk/meshfem2D.F90
   seismo/2D/SPECFEM2D/trunk/part_unstruct.F90
Log:
added comments.

Modified: seismo/2D/SPECFEM2D/trunk/meshfem2D.F90
===================================================================
--- seismo/2D/SPECFEM2D/trunk/meshfem2D.F90	2007-06-26 00:58:53 UTC (rev 8537)
+++ seismo/2D/SPECFEM2D/trunk/meshfem2D.F90	2007-12-07 23:54:39 UTC (rev 8538)
@@ -167,8 +167,6 @@
   integer  :: edgecut
   integer  :: iproc
 
-  ! variable de test
-  integer  :: aaa
 
 
 ! ***
@@ -252,7 +250,6 @@
   call read_value_logical(IIN,IGNORE_JUNK,TURN_ANISOTROPY_ON)
   call read_value_logical(IIN,IGNORE_JUNK,TURN_ATTENUATION_ON)
   
-  print *, 'POYOP'
   if ( read_external_mesh ) then
      call read_mesh(mesh_file, nelmnts, elmnts, nnodes, num_start)
      
@@ -332,8 +329,7 @@
               num_elmnt = num_elmnt + 1
            end do
         end do
-        print *, 'POY', minval(elmnts)
-     else
+      else
         num_elmnt = 0
         do j = 1, nzread
            do i = 1, nxread
@@ -890,6 +886,9 @@
 !!$     part(:) = 0
 !!$     
 !!$  else
+ 
+! if ngnod == 9, we work on a subarray of elmnts, which represents the elements with for nodes only
+! construction of the graph
   if ( ngnod == 9 ) then
      allocate(elmnts_bis(0:ESIZE*nelmnts-1))
      do i = 0, nelmnts-1
@@ -904,23 +903,21 @@
   end if
      
   nb_edges = xadj(nelmnts)
-  
+ 
+! giving weight to edges and vertices. Currently not used.
   call read_weights(nelmnts, vwgt, nb_edges, adjwgt)
      
   if ( nproc == 1 ) then
       part(:) = 0
   else
 
+! partitioning
      select case (partitionning_method)
      case(1)
         do iproc = 0, nproc-2
            part(iproc*floor(real(nelmnts)/real(nproc)):(iproc+1)*floor(real(nelmnts)/real(nproc))-1) = iproc
         end do
         part(floor(real(nelmnts)/real(nproc))*(nproc-1):nelmnts-1) = nproc - 1
-!!$        part(0:1659) = 0
-!!$        part(1660:3258) = 1
-!!$        part(3259:4799) = 2
-!!$        print *, 'WWWWWW', nelmnts-1
         
      case(2)
 #ifdef USE_METIS
@@ -944,7 +941,7 @@
  
   end if
   
-  ! beware of fluid solid edges
+! beware of fluid solid edges : coupled elements are transfered to the same partition
   if ( ngnod == 9 ) then
      call acoustic_elastic_repartitioning (nelmnts, nnodes, elmnts_bis, nb_materials, cs, num_material, &
           nproc, part, nedges_coupled, edges_coupled)
@@ -953,17 +950,10 @@
           nproc, part, nedges_coupled, edges_coupled)
   end if
   
+! local number of each element for each partition
   call Construct_glob2loc_elmnts(nelmnts, part, nproc, glob2loc_elmnts)
   
   if ( ngnod == 9 ) then
-!!$     print *, 'POUMPOUM', nnodes, elmnts(0:8)
-!!$     print *, nodes_coords(1,elmnts(0:8)+1)
-!!$     print *, nodes_coords(2,elmnts(0:8)+1)
-!!$     print *, x(1,0), z(1,0)
-!!$     print *, x(1,1), z(1,1)
-!!$     print *, num_9(2,1,nxread,nzread), x(2,1), z(2,1)
-!!$     print *, num_9(0,1,nxread,nzread),x(0,1), z(0,1)
-    
      deallocate(nnodes_elmnts)
      deallocate(nodes_elmnts)
      allocate(nnodes_elmnts(0:nnodes-1))
@@ -977,9 +967,11 @@
      end do
   end if
   
+! local number of each node for each partition
   call Construct_glob2loc_nodes(nelmnts, nnodes, nnodes_elmnts, nodes_elmnts, part, nproc, &
        glob2loc_nodes_nparts, glob2loc_nodes_parts, glob2loc_nodes)
 
+! construct the interfaces between partitions (used for MPI assembly)
   if ( nproc /= 1 ) then
      if ( ngnod == 9 ) then
         call Construct_interfaces(nelmnts, nproc, part, elmnts_bis, xadj, adjncy, tab_interfaces, &
@@ -994,6 +986,7 @@
      print *, '05'
   end if
   
+! setting absorbing boundaries by elements instead of edges
   if ( any_abs ) then
      call merge_abs_boundaries(nelemabs, nelemabs_merge, abs_surface, abs_surface_char, abs_surface_merge, &
           ibegin_bottom,iend_bottom,ibegin_top,iend_top, &
@@ -1005,7 +998,7 @@
      print *, 'nelemabs_merge', nelemabs_merge
   end if
 
-! *** generate the database for the solver
+! *** generate the databases for the solver
 
   do iproc = 0, nproc-1
      
@@ -1152,92 +1145,6 @@
   end do
   
   
-!!$
-!!$  open(unit=15,file='OUTPUT_FILES/Database',status='unknown')
-!!$
-
-!!$
-!!$  npgeo = nnodes
-!!$  nspec = nelmnts
-!!$  
-
-!!$  do j=0,nz
-!!$    do i=0,nx
-!!$      write(15,*) num(i,j,nx),x(i,j),z(i,j)
-!!$    enddo
-!!$  enddo
-!!$
-!!$
-!!$
-!!$
-!!$  
-
-!!$
-
-!!$
-!!$  k = 0
-!!$  if(ngnod == 4) then
-!!$    do j=0,nz-1
-!!$      do i=0,nx-1
-!!$        k = k + 1
-!!$        imaterial_number = num_material(i+1,j+1)
-!!$        write(15,*) k,imaterial_number,num(i,j,nx),num(i+1,j,nx),num(i+1,j+1,nx),num(i,j+1,nx)
-!!$      enddo
-!!$    enddo
-!!$  else
-!!$    do j=0,nz-2,2
-!!$      do i=0,nx-2,2
-!!$        k = k + 1
-!!$        imaterial_number = num_material(i+1,j+1)
-!!$        write(15,*) k,imaterial_number,num(i,j,nx),num(i+2,j,nx),num(i+2,j+2,nx),num(i,j+2,nx), &
-!!$                      num(i+1,j,nx),num(i+2,j+1,nx),num(i+1,j+2,nx),num(i,j+1,nx),num(i+1,j+1,nx)
-!!$      enddo
-!!$    enddo
-!!$  endif
-!!$
-!!$!
-!!$!--- save absorbing boundaries
-!!$!
-!!$  print *
-!!$  print *,'There is a total of ',nelemabs,' absorbing elements'
-!!$  print *
-!!$  print *,'Active absorbing boundaries:'
-!!$  print *
-!!$  print *,'Bottom = ',absbottom
-!!$  print *,'Right  = ',absright
-!!$  print *,'Top    = ',abstop
-!!$  print *,'Left   = ',absleft
-!!$  print *
-!!$
-!!$
-!!$
-!!$!
-!!$!--- save acoustic free-surface elements
-!!$!
-!!$  print *
-!!$  print *,'There is a total of ',nelem_acoustic_surface,' acoustic free-surface elements'
-!!$  print *
-!!$
-!!$! generate the list of acoustic free-surface elements
-!!$  if(nelem_acoustic_surface > 0) then
-!!$    write(15,*) 'List of acoustic free-surface elements:'
-!!$    do j = 1,nzread
-!!$      do i = 1,nxread
-!!$        inumelem = (j-1)*nxread + i
-!!$        if(ngnod == 4) then
-!!$          imaterial_number = num_material(i,j)
-!!$        else
-!!$          imaterial_number = num_material(2*(i-1)+1,2*(j-1)+1)
-!!$        endif
-!!$! in this simple mesher, it is always the top edge that is at the free surface
-!!$        if(icodemat(imaterial_number) /= ANISOTROPIC_MATERIAL .and. cs(imaterial_number) < TINYVAL .and. j == nzread) &
-!!$          write(15,*) inumelem,ITOP
-!!$      enddo
-!!$    enddo
-!!$  endif
-!!$
-!!$  close(15)
-!!$
 ! print position of the source
   print *
   print *,'Position (x,z) of the source = ',xs,zs

Modified: seismo/2D/SPECFEM2D/trunk/part_unstruct.F90
===================================================================
--- seismo/2D/SPECFEM2D/trunk/part_unstruct.F90	2007-06-26 00:58:53 UTC (rev 8537)
+++ seismo/2D/SPECFEM2D/trunk/part_unstruct.F90	2007-12-07 23:54:39 UTC (rev 8538)
@@ -42,7 +42,9 @@
   end subroutine read_mesh
 
 
-
+  !-----------------------------------------------
+  ! Read the nodes coordinates and storing it in array 'nodes_coords'
+  !-----------------------------------------------
   subroutine read_nodes_coords(filename, nnodes, nodes_coords)
     
     character(len=256), intent(in)  :: filename
@@ -65,7 +67,9 @@
   end subroutine read_nodes_coords
 
 
-
+  !-----------------------------------------------
+  ! Read the material for each element and storing it in array 'num_materials'
+  !-----------------------------------------------
   subroutine read_mat(filename, nelmnts, num_material)
     
     character(len=256), intent(in)  :: filename
@@ -86,7 +90,12 @@
   end subroutine read_mat
 
 
-
+  !-----------------------------------------------
+  ! Read free surface.
+  ! Edges from elastic elements are discarded.
+  ! 'acoustic_surface' contains 1/ element number, 2/ number of nodes that form the free surface,
+  ! 3/ first node on the free surface, 4/ second node on the free surface, if relevant (if 2/ is equal to 2)
+  !-----------------------------------------------
   subroutine read_acoustic_surface(filename, nelem_acoustic_surface, acoustic_surface, &
        nelmnts, num_material, ANISOTROPIC_MATERIAL, nb_materials, icodemat, cs, num_start)
     
@@ -112,7 +121,6 @@
     
     open(unit=993, file=trim(filename), form='formatted' , status='old', action='read')
     read(993,*) nelmnts_surface
-    print *, 'POY', nelmnts_surface
     
     allocate(acoustic_surface_tmp(4,nelmnts_surface))
     
@@ -150,7 +158,11 @@
   end subroutine read_acoustic_surface
   
   
-  
+  !-----------------------------------------------
+  ! Read absorbing surface.
+  ! 'abs_surface' contains 1/ element number, 2/ number of nodes that form the abs surface,
+  ! 3/ first node on the abs surface, 4/ second node on the abs surface, if relevant (if 2/ is equal to 2)
+  !-----------------------------------------------  
  subroutine read_abs_surface(filename, nelemabs, abs_surface, num_start)
     
     include './constants.h'
@@ -185,12 +197,9 @@
 
 
 
-  !*************************************************************************
-  ! creation du graphe dual (adjacence des elements definie par au moins un noeud commun )
-  !**************************************************************************
-  ! Version qui construit les adjacences en commencant par dresser la liste des elements pour chaque noeud (vertices).
-  ! On passe en plus en argument le tableau alloue qui contiendra la liste des elements par noeud, accompagne de la liste du
-  ! nombre d'elements qui contiennent chaque noeud (c'est pour pouvoir faire l'allocation avant sans connaitre la taille exacte).
+  !-----------------------------------------------
+  ! Creating dual graph (adjacency is defined by 'ncommonnodes' between two elements).
+  !-----------------------------------------------
   subroutine mesh2dual_ncommonnodes(nelmnts, nnodes, elmnts, xadj, adjncy, nnodes_elmnts, nodes_elmnts, ncommonnodes)
 
     integer, intent(in)  :: nelmnts
@@ -220,7 +229,7 @@
 
     nb_edges = 0
 
-    ! remplissage de la liste des elements par noeuds
+    ! list of elements per node
     do i = 0, esize*nelmnts-1
        nodes_elmnts(elmnts(i)*nsize+nnodes_elmnts(elmnts(i))) = i/esize
        nnodes_elmnts(elmnts(i)) = nnodes_elmnts(elmnts(i)) + 1
@@ -228,10 +237,8 @@
     end do
 
     print *, 'nnodes_elmnts'
-    !print *, nnodes_elmnts
 
-    ! pour chaque noeud, remplissage du tableau des adjacences, 
-    ! avec verification qu'un element ne soit pas compte plusieurs fois comme voisins d'un autre.
+    ! checking which elements are neighbours ('ncommonnodes' criteria)
     do j = 0, nnodes-1
        do k = 0, nnodes_elmnts(j)-1
           do l = k+1, nnodes_elmnts(j)-1
@@ -271,8 +278,7 @@
        end do
     end do
 
-    ! maintenant que la liste d'adjacence est contruite, on va refondre les tableaux dadjncy et dxadj pour qu'ils 
-    ! soient au bon format  
+    ! making adjacency arrays compact (to be used for partitioning)
     do i = 0, nelmnts-1
        k = xadj(i)
        xadj(i) = nb_edges
@@ -289,6 +295,9 @@
 
 
 
+  !-----------------------------------------------
+  ! Read the weight for each vertices and edges of the graph (not curretly used)
+  !-----------------------------------------------
   subroutine read_weights(nelmnts, vwgt, nb_edges, adjwgt)
     
     integer, intent(in)  :: nelmnts, nb_edges 
@@ -305,9 +314,9 @@
   
 
 
-  !*************************************************************************
-  ! construction du tableau de correspondance entre numerotation globale et locale (pour les elements)
-  !*************************************************************************/
+  !--------------------------------------------------
+  ! construct local numbering for the elements in each partition
+  !--------------------------------------------------
   subroutine Construct_glob2loc_elmnts(nelmnts, part, nparts, glob2loc_elmnts)
 
     integer, intent(in)  :: nelmnts, nparts
@@ -337,9 +346,9 @@
 
 
 
- !*************************************************************************
-  ! construction du tableau de correspondance entre numerotation globale et locale (pour les noeuds)
-  !*************************************************************************/
+  !--------------------------------------------------
+  ! construct local numbering for the nodes in each partition
+  !--------------------------------------------------
   subroutine Construct_glob2loc_nodes(nelmnts, nnodes, nnodes_elmnts, nodes_elmnts, part, nparts, &
        glob2loc_nodes_nparts, glob2loc_nodes_parts, glob2loc_nodes)
 
@@ -363,9 +372,6 @@
 
     size_glob2loc_nodes = 0
 
-!!$    do num_part = 0, nparts-1
-!!$       parts_node(num_part) = 0
-!!$    end do
     parts_node(:) = 0
 
 
@@ -388,36 +394,23 @@
 
 
     glob2loc_nodes_nparts(nnodes) = size_glob2loc_nodes 
-    !print *, glob2loc_nodes_nparts
-    !print *, glob2loc_nodes_nparts(nnodes)
 
-
     allocate(glob2loc_nodes_parts(0:glob2loc_nodes_nparts(nnodes)-1))
     allocate(glob2loc_nodes(0:glob2loc_nodes_nparts(nnodes)-1))
 
     glob2loc_nodes(0) = 0
 
-!!$    do num_part = 0, nparts-1
-!!$       parts_node(num_part) = 0
-!!$       num_parts(num_part) = 0
-!!$
-!!$    end do
     parts_node(:) = 0
     num_parts(:) = 0
     size_glob2loc_nodes = 0
 
 
     do num_node = 0, nnodes-1
-       !print *, 'num_node', num_node 
        do el = 0, nnodes_elmnts(num_node)-1
-          !print *, 'el_', el
           parts_node(part(nodes_elmnts(el+nsize*num_node))) = 1
 
        end do
-       !print *, 'PPP' 
        do num_part = 0, nparts-1
-          !print *, 'num_part', num_part 
-          !print *, 'parts_nodes(num_part)', parts_node(num_part) 
 
           if ( parts_node(num_part) == 1 ) then
              glob2loc_nodes_parts(size_glob2loc_nodes) = num_part
@@ -426,7 +419,6 @@
              num_parts(num_part) = num_parts(num_part) + 1
              parts_node(num_part) = 0
           end if
-          !print *, 'num_part__', num_part 
 
        end do
     end do
@@ -436,6 +428,13 @@
 
 
 
+  !--------------------------------------------------
+  ! Construct interfaces between each partitions.
+  ! Two adjacent elements in distinct partitions make an entry in array tab_interfaces : 
+  ! 1/ first element, 2/ second element, 3/ number of common nodes, 4/ first node, 
+  ! 5/ second node, if relevant.
+  ! No interface between acoustic and elastic elements.
+  !--------------------------------------------------
   subroutine Construct_interfaces(nelmnts, nparts, part, elmnts, xadj, adjncy, tab_interfaces, &
        tab_size_interfaces, ninterfaces, nb_materials, cs_material, num_material)
 
@@ -458,7 +457,7 @@
     integer  :: i, j
     logical  :: is_acoustic_el, is_acoustic_el_adj
 
-    print *, '00'
+
     ninterfaces = 0
     do  i = 0, nparts-1
        do j = i+1, nparts-1
@@ -469,11 +468,10 @@
     allocate(tab_size_interfaces(0:ninterfaces))
     tab_size_interfaces(:) = 0
 
-    print *, 'num_interface', ninterfaces
+!    print *, 'num_interface', ninterfaces
 
     num_interface = 0
     num_edge = 0
-    print *, '01'
 
     do num_part = 0, nparts-1
        do num_part_bis = num_part+1, nparts-1
@@ -498,24 +496,19 @@
                 end do
              end if
           end do
-          print *, 'num_interface', num_interface
+!          print *, 'num_interface', num_interface
           tab_size_interfaces(num_interface+1) = tab_size_interfaces(num_interface) + num_edge 
           num_edge = 0
           num_interface = num_interface + 1
 
        end do
     end do
-    print *, 'POUM',tab_size_interfaces(num_interface)
 
     num_interface = 0
     num_edge = 0
 
-    print *, '02'
-
-    ! le 5 vient du fait que l'on represente l'interface comme un tableau avec 5 valeurs: element1-element2-valence-noeud1-noeud2
     allocate(tab_interfaces(0:(tab_size_interfaces(ninterfaces)*5-1)))
     tab_interfaces(:) = 0
-    print *, '03'
 
     do num_part = 0, nparts-1
        do num_part_bis = num_part+1, nparts-1
@@ -566,7 +559,9 @@
   end subroutine Construct_interfaces
 
 
-
+  !--------------------------------------------------
+  ! Write nodes (their coordinates) pertaining to iproc partition in the corresponding Database
+  !--------------------------------------------------
   subroutine write_glob2loc_nodes_database(IIN_database, iproc, npgeo, nodes_coords, glob2loc_nodes_nparts, glob2loc_nodes_parts, & 
        glob2loc_nodes, nnodes, num_phase)
     
@@ -590,7 +585,6 @@
                 npgeo = npgeo + 1
                 
              end if
-             !write(992,*) i, glob2loc_nodes_parts(j), glob2loc_nodes(j)
              
           end do
        end do
@@ -608,6 +602,9 @@
 
 
 
+  !--------------------------------------------------
+  ! Write elements (their nodes) pertaining to iproc partition in the corresponding Database
+  !--------------------------------------------------
   subroutine write_partition_database(IIN_database, iproc, nspec, nelmnts, elmnts, glob2loc_elmnts, glob2loc_nodes_nparts, &
      glob2loc_nodes_parts, glob2loc_nodes, part, num_modele, ngnod, num_phase)
 
@@ -659,6 +656,9 @@
 
 
 
+  !--------------------------------------------------
+  ! Write interfaces (element and common nodes) pertaining to iproc partition in the corresponding Database
+  !--------------------------------------------------
   subroutine Write_interfaces_database(IIN_database, tab_interfaces, tab_size_interfaces, nparts, iproc, ninterfaces, &
        my_ninterface, my_interfaces, my_nb_interfaces, glob2loc_elmnts, glob2loc_nodes_nparts, glob2loc_nodes_parts, &
        glob2loc_nodes, num_phase)
@@ -767,6 +767,9 @@
 
 
 
+  !--------------------------------------------------
+  ! Write a surface (elements and nodes on the surface) pertaining to iproc partition in the corresponding Database
+  !--------------------------------------------------
  subroutine Write_surface_database(IIN_database, nsurface, surface, &
       nsurface_loc, nparts, iproc, glob2loc_elmnts, &
       glob2loc_nodes_nparts, glob2loc_nodes_parts, glob2loc_nodes, part, num_phase)
@@ -854,6 +857,12 @@
 
 
 
+  !--------------------------------------------------
+  ! Set absorbing boundaries by elements instead of edges.
+  ! Excludes points that have both absorbing condition and coupled fluid/solid relation (this is the 
+  ! reason arrays ibegin_..., iend_... were included here).
+  ! Under development : exluding points that have two different normal.
+  !--------------------------------------------------
      subroutine merge_abs_boundaries(nelemabs, nelemabs_merge, abs_surface, abs_surface_char, abs_surface_merge, &
           ibegin_bottom,iend_bottom,ibegin_top,iend_top, &
           jbegin_left,jend_left,jbegin_right,jend_right, &
@@ -1226,20 +1235,13 @@
 
         end do
 
-!!$print *, 'AAAAAAAAa'
-!!$        do iedge = 1, nedges_coupled
-!!$           print *, nodes_coords(1,elmnts(ngnod*edges_coupled(1,iedge))+1), &
-!!$                nodes_coords(2,elmnts(ngnod*edges_coupled(1,iedge))+1), 0
-!!$           print *, nodes_coords(1,elmnts(ngnod*edges_coupled(2,iedge))+1), &
-!!$                nodes_coords(2,elmnts(ngnod*edges_coupled(2,iedge))+1), 0
-!!$           
-!!$        end do
-!!$print *, 'AAAAAAAAa'       
 
      end subroutine merge_abs_boundaries
      
      
-     
+  !--------------------------------------------------
+  ! Write abs surface (elements and nodes on the surface) pertaining to iproc partition in the corresponding Database
+  !--------------------------------------------------     
      subroutine write_abs_merge_database(IIN_database, nelemabs_merge, nelemabs_loc, &
           abs_surface_char, abs_surface_merge, &
           ibegin_bottom,iend_bottom,ibegin_top,iend_top, &
@@ -1292,6 +1294,9 @@
     
      
 #ifdef USE_METIS
+  !--------------------------------------------------
+  ! Partitioning using METIS
+  !--------------------------------------------------
      subroutine Part_metis(nelmnts, xadj, adjncy, vwgt, adjwgt, nparts, nb_edges, edgecut, part, metis_options)
 
     integer, intent(in)  :: nelmnts, nparts, nb_edges 
@@ -1323,6 +1328,9 @@
 
 
 #ifdef USE_SCOTCH
+  !--------------------------------------------------
+  ! Partitioning using SCOTCH
+  !--------------------------------------------------
   subroutine Part_scotch(nelmnts, xadj, adjncy, vwgt, adjwgt, nparts, nedges, edgecut, part, scotch_strategy)
     
     include 'scotchf.h'
@@ -1351,18 +1359,7 @@
        STOP
     ENDIF
     
-    !scotch_strategy="b{strat=x}"
-    !scotch_strategy='b{strat=h{pass=10000}}'
-    !scotch_strategy='b{strat=m{asc=b{strat=g{pass=100}},low=g{pass=100},type=h,vert=10}}'
-    !scotch_strategy='b{strat=f{bal=0.0001,move=1000000,pass=-1}}'
-    !scotch_strategy='b{strat=g}'
-    !scotch_strategy='g'
-    !scotch_strategy='b{strat=hf{move=1000}}'
-    !scotch_strategy='b{strat=m{vert=4,asc=h|g,low=f}}'
-    !scotch_strategy='b{strat=m{asc=g,low=g,rat=1.0,type=h,vert=4}}'
-    !scotch_strategy='b{strat=m{asc=g,low=f{bal=0.001,move=10000,pass=500},rat=0.5,type=h,vert=4}}'
     call scotchfstratgraphmap (SCOTCHSTRAT(1), trim(scotch_strategy), IERR)
-    !call scotchfstratgraphbipart (SCOTCHSTRAT(1), trim(scotch_strategy), IERR)
      IF (IERR .NE. 0) THEN
        PRINT *, 'ERROR : MAIN : Cannot build strat'
        STOP
@@ -1415,6 +1412,9 @@
 
 
 
+  !--------------------------------------------------
+  ! Repartitioning : two coupled acoustic/elastic elements are transfered to the same partition
+  !--------------------------------------------------
 subroutine acoustic_elastic_repartitioning (nelmnts, nnodes, elmnts, nb_materials, cs_material, num_material, &
      nproc, part, nedges_coupled, edges_coupled)
        
@@ -1455,13 +1455,6 @@
 
   call mesh2dual_ncommonnodes(nelmnts, nnodes, elmnts, xadj, adjncy, nnodes_elmnts, nodes_elmnts,2)
 
-!!$  aaa = 1600
-!!$  print *, 'POUM', xadj(aaa), xadj(aaa+1) - 1
-!!$  do i =  xadj(aaa),  xadj(aaa+1) -1
-!!$     print *, i, adjncy(i)
-!!$  end do
-!!$  stop
-
   nedges_coupled = 0
   do el = 0, nelmnts-1
      if ( is_acoustic(num_material(el+1)) ) then
@@ -1515,6 +1508,10 @@
   
 
 
+  !--------------------------------------------------
+  ! Write fluid/solid edges (fluid elements and corresponding solid elements) 
+  ! pertaining to iproc partition in the corresponding Database
+  !--------------------------------------------------     
 subroutine write_fluidsolid_edges_database(IIN_database, nedges_coupled, nedges_coupled_loc, &
      edges_coupled, glob2loc_elmnts, nelmnts,part, iproc, num_phase)
        



More information about the cig-commits mailing list