[cig-commits] r14167 - seismo/3D/SPECFEM3D_SESAME/trunk/UTILS/external_mesh/pre_meshfem3D_asteroid_subdivide

pieyre at geodynamics.org pieyre at geodynamics.org
Fri Feb 27 05:21:45 PST 2009


Author: pieyre
Date: 2009-02-27 05:21:40 -0800 (Fri, 27 Feb 2009)
New Revision: 14167

Added:
   seismo/3D/SPECFEM3D_SESAME/trunk/UTILS/external_mesh/pre_meshfem3D_asteroid_subdivide/scotchf.h
Modified:
   seismo/3D/SPECFEM3D_SESAME/trunk/UTILS/external_mesh/pre_meshfem3D_asteroid_subdivide/compil_all.sh
   seismo/3D/SPECFEM3D_SESAME/trunk/UTILS/external_mesh/pre_meshfem3D_asteroid_subdivide/constants_pre_meshfem3D.h
   seismo/3D/SPECFEM3D_SESAME/trunk/UTILS/external_mesh/pre_meshfem3D_asteroid_subdivide/part_pre_meshfem3D.f90
   seismo/3D/SPECFEM3D_SESAME/trunk/UTILS/external_mesh/pre_meshfem3D_asteroid_subdivide/pre_meshfem3D.f90
Log:
added SCOTCH partitioner, for good.

Modified: seismo/3D/SPECFEM3D_SESAME/trunk/UTILS/external_mesh/pre_meshfem3D_asteroid_subdivide/compil_all.sh
===================================================================
--- seismo/3D/SPECFEM3D_SESAME/trunk/UTILS/external_mesh/pre_meshfem3D_asteroid_subdivide/compil_all.sh	2009-02-27 02:08:44 UTC (rev 14166)
+++ seismo/3D/SPECFEM3D_SESAME/trunk/UTILS/external_mesh/pre_meshfem3D_asteroid_subdivide/compil_all.sh	2009-02-27 13:21:40 UTC (rev 14167)
@@ -7,6 +7,7 @@
 
 gfortran -c part_pre_meshfem3D.f90
 gfortran -c pre_meshfem3D.f90
-gfortran pre_meshfem3D.o part_pre_meshfem3D.o ~/utils/metis-4.0/libmetis.a
+#gfortran pre_meshfem3D.o part_pre_meshfem3D.o ~/utils/metis-4.0/libmetis.a
 #gfortran pre_meshfem3D.o part_pre_meshfem3D.o ~/utils/scotch_5.1/lib/libscotchmetis.a ~/utils/scotch_5.1/lib/libscotch.a ~/utils/scotch_5.1/lib/libscotcherr.a
-#gfortran pre_meshfem3D.o part_pre_meshfem3D.o ~/utils/scotch_5.1/lib/libscotch.a ~/utils/scotch_5.1/lib/libscotcherr.a
+gfortran pre_meshfem3D.o part_pre_meshfem3D.o ~/utils/scotch_5.1/lib/libscotch.a ~/utils/scotch_5.1/lib/libscotcherr.a
+

Modified: seismo/3D/SPECFEM3D_SESAME/trunk/UTILS/external_mesh/pre_meshfem3D_asteroid_subdivide/constants_pre_meshfem3D.h
===================================================================
--- seismo/3D/SPECFEM3D_SESAME/trunk/UTILS/external_mesh/pre_meshfem3D_asteroid_subdivide/constants_pre_meshfem3D.h	2009-02-27 02:08:44 UTC (rev 14166)
+++ seismo/3D/SPECFEM3D_SESAME/trunk/UTILS/external_mesh/pre_meshfem3D_asteroid_subdivide/constants_pre_meshfem3D.h	2009-02-27 13:21:40 UTC (rev 14167)
@@ -1,3 +1,5 @@
+! Useful kind types
+integer ,parameter :: short = SELECTED_INT_KIND(4), long = SELECTED_INT_KIND(18)
 
 ! Number of nodes per elements.
 integer, parameter  :: ESIZE = 8
@@ -5,11 +7,5 @@
 ! Number of faces per element.
 integer, parameter  :: nfaces = 6
 
-! Max number of neighbours per elements.
-!  integer, parameter  :: max_neighbour=60
-
-! Max number of elements that can contain the same node.
-!  integer, parameter  :: nsize=20
-
 ! very large and very small values
   double precision, parameter :: HUGEVAL = 1.d+30,TINYVAL = 1.d-9

Modified: seismo/3D/SPECFEM3D_SESAME/trunk/UTILS/external_mesh/pre_meshfem3D_asteroid_subdivide/part_pre_meshfem3D.f90
===================================================================
--- seismo/3D/SPECFEM3D_SESAME/trunk/UTILS/external_mesh/pre_meshfem3D_asteroid_subdivide/part_pre_meshfem3D.f90	2009-02-27 02:08:44 UTC (rev 14166)
+++ seismo/3D/SPECFEM3D_SESAME/trunk/UTILS/external_mesh/pre_meshfem3D_asteroid_subdivide/part_pre_meshfem3D.f90	2009-02-27 13:21:40 UTC (rev 14167)
@@ -12,10 +12,10 @@
 
     include './constants_pre_meshfem3D.h'
 
-    integer, intent(in)  :: nelmnts
+    integer(long), intent(in)  :: nelmnts
     integer, intent(in)  :: nnodes
-    integer, intent(in)  :: nsize
-    integer, intent(in)  :: sup_neighbour
+    integer(long), intent(in)  :: nsize
+    integer(long), intent(in)  :: sup_neighbour
     integer, dimension(0:esize*nelmnts-1), intent(in)  :: elmnts 
     integer, dimension(0:nelmnts)  :: xadj
     integer, dimension(0:sup_neighbour*nelmnts-1)  :: adjncy
@@ -50,7 +50,7 @@
 
     end do
 
-    print *, 'nnodes_elmnts'
+    !print *, 'nnodes_elmnts'
 
     ! checking which elements are neighbours ('ncommonnodes' criteria)
     do j = 0, nnodes-1
@@ -120,14 +120,14 @@
     
     include './constants_pre_meshfem3D.h'
 
-    integer, intent(in)  :: nelmnts, nparts
+    integer(long), intent(in)  :: nelmnts
+    integer, intent(in)  :: nparts
     integer, dimension(0:nelmnts-1), intent(in)  :: part
     integer, dimension(:), pointer  :: glob2loc_elmnts
 
     integer  :: num_glob, num_part
     integer, dimension(0:nparts-1)  :: num_loc
 
-    print *, "AAAAA"
 
     allocate(glob2loc_elmnts(0:nelmnts-1))
 
@@ -156,7 +156,8 @@
 
     include './constants_pre_meshfem3D.h'
 
-    integer, intent(in)  :: nelmnts, nnodes, nparts, nsize
+    integer(long), intent(in)  :: nelmnts, nsize
+    integer, intent(in)  :: nnodes, nparts
     integer, dimension(0:nelmnts-1), intent(in)  :: part
     integer, dimension(0:nnodes-1), intent(in)  :: nnodes_elmnts
     integer, dimension(0:nsize*nnodes-1), intent(in)  :: nodes_elmnts
@@ -242,7 +243,8 @@
 
      include './constants_pre_meshfem3D.h'
 
-    integer, intent(in)  :: nelmnts, nparts, sup_neighbour
+    integer, intent(in)  :: nparts
+    integer(long), intent(in)  :: nelmnts, sup_neighbour
     integer, dimension(0:nelmnts-1), intent(in)  :: part
     integer, dimension(0:esize*nelmnts-1), intent(in)  :: elmnts
     integer, dimension(0:nelmnts), intent(in)  :: xadj
@@ -408,7 +410,8 @@
     include './constants_pre_meshfem3D.h'
 
     integer, intent(in)  :: IIN_database
-    integer, intent(in)  :: nelmnts, num_phase, iproc
+    integer, intent(in)  :: num_phase, iproc
+    integer(long), intent(in)  :: nelmnts
     integer, intent(inout)  :: nspec
     integer, dimension(0:nelmnts-1)  :: part
     integer, dimension(0:esize*nelmnts-1)  :: elmnts

Modified: seismo/3D/SPECFEM3D_SESAME/trunk/UTILS/external_mesh/pre_meshfem3D_asteroid_subdivide/pre_meshfem3D.f90
===================================================================
--- seismo/3D/SPECFEM3D_SESAME/trunk/UTILS/external_mesh/pre_meshfem3D_asteroid_subdivide/pre_meshfem3D.f90	2009-02-27 02:08:44 UTC (rev 14166)
+++ seismo/3D/SPECFEM3D_SESAME/trunk/UTILS/external_mesh/pre_meshfem3D_asteroid_subdivide/pre_meshfem3D.f90	2009-02-27 13:21:40 UTC (rev 14167)
@@ -4,16 +4,13 @@
   implicit none
   
   include './constants_pre_meshfem3D.h'
+  include "./scotchf.h"
 
-!!!! NL NL for SCOTCH
-!  include "./scotchf.h"
-!!!!
 
-
-  integer, parameter  :: nparts=2
+  integer, parameter  :: nparts=8
   
 
-  integer :: nspec
+  integer(long) :: nspec
   integer, dimension(:,:), allocatable  :: elmnts
   integer, dimension(:), allocatable  :: mat
   integer, dimension(:), allocatable  :: part
@@ -45,7 +42,7 @@
   double precision, dimension(:), allocatable :: cs
   integer, dimension(:), allocatable :: num_material
 
-  integer  :: nsize  ! Max number of elements that contain the same node.
+  integer(long)  :: nsize  ! Max number of elements that contain the same node.
   integer  :: edgecut
   integer  :: nb_edges
 
@@ -54,7 +51,7 @@
   integer  :: num_start
   integer  :: ngnod
   integer  :: max_neighbour   ! Real maximum number of neighbours per element
-  integer  :: sup_neighbour   ! Majoration of the maximum number of neighbours per element
+  integer(long)  :: sup_neighbour   ! Majoration of the maximum number of neighbours per element
 
   integer  :: ipart, nnodes_loc, nspec_loc
   character(len=256)  :: prname
@@ -63,13 +60,10 @@
   integer, dimension(:), allocatable :: used_nodes_elmnts
 
 !!!! NL NL for SCOTCH partitioner
-!  double precision, dimension(SCOTCH_GRAPHDIM)  :: SCOTCHGRAPH
-!  double precision, dimension(SCOTCH_STRATDIM)  :: SCOTCHSTRAT
-!  character(len=256), parameter ::
-!scotch_strategy='b{sep=m{vert=100,low=h,asc=f}x}'
-!  !character(len=256), parameter ::
-!scotch_strategy='b{strat=m{asc=g,low=g,rat=1.0,type=h,vert=4}}'
-!  integer  :: IERR
+ double precision, dimension(SCOTCH_GRAPHDIM)  :: scotchgraph
+ double precision, dimension(SCOTCH_STRATDIM)  :: scotchstrat
+ character(len=256), parameter :: scotch_strategy='b{job=t,map=t,poli=S,sep=h{pass=30}}'
+ integer  :: ierr
 !!!! NL NL
 
 
@@ -110,12 +104,10 @@
       used_nodes_elmnts(elmnts(inode,ispec)) = used_nodes_elmnts(elmnts(inode,ispec)) + 1
     enddo
   enddo
-  !PLL
   nsize = maxval(used_nodes_elmnts(:))
   sup_neighbour = ngnod * nsize - (ngnod + (ngnod/2 - 1)*nfaces)
   print*, 'nsize = ',nsize, 'sup_neighbour = ', sup_neighbour
 
-  print *, minval(used_nodes_elmnts(:)), maxval(used_nodes_elmnts(:))
   do inode = 1, nnodes
     if (.not. mask_nodes_elmnts(inode)) then
       stop 'ERROR : nodes not used.'
@@ -140,82 +132,71 @@
  ! elmnts(:,:) = elmnts(:,:) + 1
  ! adjncy(:) = adjncy(:) + 1
  ! xadj(:) = xadj(:) + 1
-  allocate(vwgt(0:nspec-1))
+!  allocate(vwgt(0:nspec-1))
   nb_edges = xadj(nspec+1)
-  allocate(adjwgt(0:nb_edges-1))
-  vwgt(:) = 1
-  adjwgt(:) = 1
+!   allocate(adjwgt(0:nb_edges-1))
+!   vwgt(:) = 1
+!   adjwgt(:) = 1
 
-  metis_options(1) = 0
-  metis_options(2) = 3
-  metis_options(3) = 1
-  metis_options(4) = 1
-  metis_options(5) = 0
+!   metis_options(1) = 0
+!   metis_options(2) = 3
+!   metis_options(3) = 1
+!   metis_options(4) = 1
+!   metis_options(5) = 0
   
   
-  num_start = 0
-  wgtflag = 0
+!   num_start = 0
+!   wgtflag = 0
 
   allocate(part(1:nspec))
 
 
-! partitioning
-  call METIS_PartGraphRecursive(nspec, xadj(1), adjncy(1), vwgt(0), adjwgt(0), wgtflag, num_start, nparts, &
-       metis_options, edgecut, part(1));
+! Old metis partitioning
+!   call METIS_PartGraphRecursive(nspec, xadj(1), adjncy(1), vwgt(0), adjwgt(0), wgtflag, num_start, nparts, &
+!        metis_options, edgecut, part(1));
  
-!!!! NL NL for SCOTCH partitioner
-!!$    call scotchfstratinit (SCOTCHSTRAT(1), IERR)
-!!$     IF (IERR .NE. 0) THEN
-!!$       PRINT *, 'ERROR : MAIN : Cannot initialize strat'
-!!$       STOP
-!!$    ENDIF
-!!$
-!!$    call scotchfstratgraphmap (SCOTCHSTRAT(1), trim(scotch_strategy), IERR)
-!!$     IF (IERR .NE. 0) THEN
-!!$       PRINT *, 'ERROR : MAIN : Cannot build strat'
-!!$       STOP
-!!$    ENDIF
-!!$    CALL SCOTCHFGRAPHINIT (SCOTCHGRAPH (1), IERR)
-!!$    IF (IERR .NE. 0) THEN
-!!$       PRINT *, 'ERROR : MAIN : Cannot initialize graph'
-!!$       STOP
-!!$    ENDIF
-!!$
-!!$    CALL SCOTCHFGRAPHBUILD (SCOTCHGRAPH (1), 0, nspec, &
-!!$         xadj (1), xadj (1), &
-!!$         xadj (1), xadj (1), &
-!!$         nb_edges, &
-!!$         adjncy (1), adjncy (1), IERR)
-!!$    IF (IERR .NE. 0) THEN
-!!$       PRINT *, 'ERROR : MAIN : Cannot build graph'
-!!$       STOP
-!!$    ENDIF
-!!$
-!!$    CALL SCOTCHFGRAPHCHECK (SCOTCHGRAPH (1), IERR)
-!!$    IF (IERR .NE. 0) THEN
-!!$       PRINT *, 'ERROR : MAIN : Invalid check'
-!!$       STOP
-!!$    ENDIF
-!!$
-!!$    call scotchfgraphpart (SCOTCHGRAPH (1), nparts, SCOTCHSTRAT(1),part(1),IERR)
-!!$    IF (IERR .NE. 0) THEN
-!!$       PRINT *, 'ERROR : MAIN : Cannot part graph'
-!!$       STOP
-!!$    ENDIF
-!!$
-!!$    CALL SCOTCHFGRAPHEXIT (SCOTCHGRAPH (1), IERR)
-!!$    IF (IERR .NE. 0) THEN
-!!$       PRINT *, 'ERROR : MAIN : Cannot destroy graph'
-!!$       STOP
-!!$    ENDIF
-!!$
-!!$    call scotchfstratexit (SCOTCHSTRAT(1), IERR)
-!!$    IF (IERR .NE. 0) THEN
-!!$       PRINT *, 'ERROR : MAIN : Cannot destroy strat'
-!!$       STOP
-!!$    ENDIF
-!!!! NL NL
+! SCOTCH partitioning
+    call scotchfstratinit (scotchstrat(1), ierr)
+     if (ierr /= 0) then
+       stop 'ERROR : MAIN : Cannot initialize strat'
+    endif
 
+    call scotchfstratgraphmap (scotchstrat(1), trim(scotch_strategy), ierr)
+     if (ierr /= 0) then
+       stop 'ERROR : MAIN : Cannot build strat'
+    endif
+
+    call scotchfgraphinit (scotchgraph (1), ierr)
+    if (ierr /= 0) then
+       stop 'ERROR : MAIN : Cannot initialize graph'
+    endif
+
+    call scotchfgraphbuild (scotchgraph (1), 0, nspec, xadj (1), xadj (1), &
+         xadj (1), xadj (1), nb_edges, adjncy (1), adjncy (1), ierr)
+    if (ierr /= 0) then
+       stop 'ERROR : MAIN : Cannot build graph'
+    endif
+
+    call scotchfgraphcheck (scotchgraph (1), ierr)
+    if (ierr /= 0) then
+       stop 'ERROR : MAIN : Invalid check'
+    endif
+
+    call scotchfgraphpart (scotchgraph (1), nparts, scotchstrat(1),part(1),ierr)
+    if (ierr /= 0) then
+       stop 'ERROR : MAIN : Cannot part graph'
+    endif
+
+    call scotchfgraphexit (scotchgraph (1), ierr)
+    if (ierr /= 0) then
+       stop 'ERROR : MAIN : Cannot destroy graph'
+    endif
+
+    call scotchfstratexit (scotchstrat(1), ierr)
+    if (ierr /= 0) then
+       stop 'ERROR : MAIN : Cannot destroy strat'
+    endif
+
  
 ! local number of each element for each partition
   call Construct_glob2loc_elmnts(nspec, part, nparts, glob2loc_elmnts)

Added: seismo/3D/SPECFEM3D_SESAME/trunk/UTILS/external_mesh/pre_meshfem3D_asteroid_subdivide/scotchf.h
===================================================================
--- seismo/3D/SPECFEM3D_SESAME/trunk/UTILS/external_mesh/pre_meshfem3D_asteroid_subdivide/scotchf.h	                        (rev 0)
+++ seismo/3D/SPECFEM3D_SESAME/trunk/UTILS/external_mesh/pre_meshfem3D_asteroid_subdivide/scotchf.h	2009-02-27 13:21:40 UTC (rev 14167)
@@ -0,0 +1,19 @@
+
+        INTEGER SCOTCH_ARCHDIM
+        INTEGER SCOTCH_DGRAPHDIM
+        INTEGER SCOTCH_DORDERDIM
+        INTEGER SCOTCH_GEOMDIM
+        INTEGER SCOTCH_GRAPHDIM
+        INTEGER SCOTCH_MAPDIM
+        INTEGER SCOTCH_MESHDIM
+        INTEGER SCOTCH_ORDERDIM
+        INTEGER SCOTCH_STRATDIM
+        PARAMETER (SCOTCH_ARCHDIM   = 5)
+        PARAMETER (SCOTCH_DGRAPHDIM = 1)
+        PARAMETER (SCOTCH_DORDERDIM = 1)
+        PARAMETER (SCOTCH_GEOMDIM   = 2)
+        PARAMETER (SCOTCH_GRAPHDIM  = 12)
+        PARAMETER (SCOTCH_MAPDIM    = 13)
+        PARAMETER (SCOTCH_MESHDIM   = 15)
+        PARAMETER (SCOTCH_ORDERDIM  = 12)
+        PARAMETER (SCOTCH_STRATDIM  = 1)



More information about the CIG-COMMITS mailing list