1 |
dgoldberg |
1.1 |
C $Header: /u/gcmpack/MITgcm/pkg/streamice/streamice_petsc_numerate.F,v 1.4 2015/03/07 11:30:52 dgoldberg Exp $ |
2 |
|
|
C $Name: $ |
3 |
|
|
|
4 |
|
|
#include "CPP_OPTIONS.h" |
5 |
|
|
|
6 |
|
|
C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----| |
7 |
|
|
|
8 |
|
|
CBOP |
9 |
|
|
SUBROUTINE CG3D_PETSC_NUMERATE (myThid) |
10 |
|
|
|
11 |
|
|
C /============================================================\ |
12 |
|
|
C | SUBROUTINE | |
13 |
|
|
C | o | |
14 |
|
|
C |============================================================| |
15 |
|
|
C | | |
16 |
|
|
C \============================================================/ |
17 |
|
|
IMPLICIT NONE |
18 |
|
|
|
19 |
|
|
C === Global variables === |
20 |
|
|
#include "SIZE.h" |
21 |
|
|
#include "GRID.h" |
22 |
|
|
!#include "SURFACE.h" |
23 |
|
|
#include "EEPARAMS.h" |
24 |
|
|
#include "PARAMS.h" |
25 |
|
|
!#ifdef ALLOW_PETSC |
26 |
|
|
!#include "CG3D_PETSC.h" |
27 |
|
|
! UNCOMMENT IF V3.0 |
28 |
|
|
!#include "finclude/petscvec.h" |
29 |
|
|
!#include "finclude/petscmat.h" |
30 |
|
|
!#include "finclude/petscksp.h" |
31 |
|
|
!#include "finclude/petscpc.h" |
32 |
|
|
!#endif |
33 |
|
|
#include "CG3D.h" |
34 |
|
|
#ifdef ALLOW_USE_MPI |
35 |
|
|
#include "EESUPPORT.h" |
36 |
|
|
#endif |
37 |
|
|
|
38 |
|
|
INTEGER myThid |
39 |
|
|
|
40 |
|
|
#ifdef ALLOW_NONHYDROSTATIC |
41 |
|
|
|
42 |
|
|
INTEGER i, j, bi, bj, k, l |
43 |
|
|
CHARACTER*(MAX_LEN_MBUF) msgBuf |
44 |
|
|
#ifdef ALLOW_USE_MPI |
45 |
|
|
integer mpiRC, mpiMyWid |
46 |
|
|
#endif |
47 |
|
|
#ifdef ALLOW_PETSC |
48 |
|
|
_RS DoFCountColor (MAX_CG3D_PETSC_CPUINVERT) |
49 |
|
|
_RS DoFCountColorCumSum (MAX_CG3D_PETSC_CPUINVERT) |
50 |
|
|
! _RS DoFCount |
51 |
|
|
integer color, rank |
52 |
|
|
integer cg3d_dofs_proc_loc (0:nPx*nPy*MAX_CG3D_PETSC_CPUINVERT-1) |
53 |
|
|
integer cg3d_dofs_cum_sum (0:nPx*nPy*MAX_CG3D_PETSC_CPUINVERT-1) |
54 |
|
|
integer dofPerRank |
55 |
|
|
|
56 |
|
|
#ifdef ALLOW_USE_MPI |
57 |
|
|
CALL MPI_COMM_RANK( MPI_COMM_WORLD, mpiMyWId, mpiRC ) |
58 |
|
|
#endif |
59 |
|
|
|
60 |
|
|
dofPerRank = Nr/cg3d_petsc_cpuInVert |
61 |
|
|
|
62 |
|
|
DO l=1,MAX_CG3D_PETSC_CPUINVERT |
63 |
|
|
IF (l.le.cg3d_petsc_cpuInVert) THEN |
64 |
|
|
cg3d_color_rank (l) = mpiRC |
65 |
|
|
ENDIF |
66 |
|
|
ENDDO |
67 |
|
|
|
68 |
|
|
DO bj = myByLo(myThid), myByHi(myThid) |
69 |
|
|
DO bi = myBxLo(myThid), myBxHi(myThid) |
70 |
|
|
DO j=1,sNy |
71 |
|
|
DO i=1,sNx |
72 |
|
|
DO k=1,Nr |
73 |
|
|
cg3d_petsc_dofs (i,j,k,bi,bj) = -2.0 |
74 |
dgoldberg |
1.2 |
cg3d_petsc_color (i,j,k,bi,bj) = 1 + ((k-1) / dofPerRank) |
75 |
dgoldberg |
1.1 |
ENDDO |
76 |
|
|
ENDDO |
77 |
|
|
ENDDO |
78 |
|
|
ENDDO |
79 |
|
|
ENDDO |
80 |
|
|
|
81 |
|
|
DO k=1, MAX_CG3D_PETSC_CPUINVERT |
82 |
|
|
IF (k.le.cg3d_petsc_cpuInVert) THEN |
83 |
|
|
DoFCountColor (k) = -1.0 |
84 |
|
|
ENDIF |
85 |
|
|
ENDDO |
86 |
|
|
!DoFCount = -1.0 |
87 |
|
|
DO bj = myByLo(myThid), myByHi(myThid) |
88 |
|
|
DO bi = myBxLo(myThid), myBxHi(myThid) |
89 |
|
|
DO j=1,sNy |
90 |
|
|
DO i=1,sNx |
91 |
|
|
DO k=1,Nr |
92 |
|
|
|
93 |
|
|
|
94 |
|
|
C DOFS ARE NUMBERED AS FOLLOWS ON PROCESSOR DOMAIN: |
95 |
|
|
C grid is stepped through in order bj, bi, j, i |
96 |
|
|
C 1) if hfacc0(i,j,k,bi,bj)==1, the counter is updated by 1; |
97 |
|
|
C cg3d_petsc_dofs is assigned the counter; |
98 |
|
|
C o/w cg3d_petsc_dofs is assigned -1 |
99 |
|
|
C NOTE THESE NUMBERING ARRAYS ARE USED TO CONSTRUCT PETSC VECTORS AND MATRIX |
100 |
|
|
|
101 |
|
|
color = cg3d_petsc_color (i,j,k,bi,bj) |
102 |
|
|
|
103 |
|
|
if (_hFacC(i,j,k,bi,bj).gt.0.0) THEN |
104 |
|
|
DoFCountColor(color) = DoFCountColor(color) + 1.0 |
105 |
|
|
cg3d_petsc_dofs (i,j,k,bi,bj) = DoFCountColor(color) |
106 |
|
|
else |
107 |
|
|
cg3d_petsc_dofs (i,j,k,bi,bj) = -1.0 |
108 |
|
|
endif |
109 |
|
|
|
110 |
|
|
ENDDO |
111 |
|
|
ENDDO |
112 |
|
|
ENDDO |
113 |
|
|
ENDDO |
114 |
|
|
ENDDO |
115 |
|
|
|
116 |
|
|
DoFCountColorCumSum (1) = 0.0 |
117 |
|
|
DO k=2, MAX_CG3D_PETSC_CPUINVERT |
118 |
|
|
IF (k.le.cg3d_petsc_cpuInVert) THEN |
119 |
|
|
DoFCountColorCumSum (k) = DoFCountColorCumSum (k-1) + |
120 |
|
|
& DoFCountColor (k-1) |
121 |
|
|
ENDIF |
122 |
|
|
ENDDO |
123 |
|
|
|
124 |
|
|
|
125 |
|
|
#ifdef ALLOW_USE_MPI |
126 |
|
|
|
127 |
|
|
DO i=0,nPx*nPy*MAX_CG3D_PETSC_CPUINVERT-1 |
128 |
|
|
IF (i.le.cg3d_petsc_cpuInVert) THEN |
129 |
|
|
cg3d_dofs_proc_loc (i) = 0 |
130 |
|
|
ENDIF |
131 |
|
|
ENDDO |
132 |
|
|
|
133 |
|
|
DO l=1,MAX_CG3D_PETSC_CPUINVERT |
134 |
|
|
IF (l.le.cg3d_petsc_cpuInVert) THEN |
135 |
|
|
IF (cg3d_color_rank(l).eq.mpiMyWid) THEN |
136 |
|
|
cg3d_dofs_proc_loc (mpiMyWId) = INT(DoFCountColor(l))+1 |
137 |
|
|
ENDIF |
138 |
|
|
ENDIF |
139 |
|
|
ENDDO |
140 |
|
|
|
141 |
|
|
CALL MPI_Allreduce(cg3d_dofs_proc_loc,cg3d_dofs_process, |
142 |
|
|
& nPx*nPy*MAX_CG3D_PETSC_CPUINVERT,MPI_INTEGER, |
143 |
|
|
& MPI_SUM,MPI_COMM_MODEL,mpiRC) |
144 |
|
|
|
145 |
|
|
cg3d_dofs_cum_sum(0) = 0 |
146 |
|
|
|
147 |
|
|
DO i=1,nPx*nPy*MAX_CG3D_PETSC_CPUINVERT-1 |
148 |
|
|
IF (i.le.cg3d_petsc_cpuInVert) THEN |
149 |
|
|
cg3d_dofs_cum_sum(i) = cg3d_dofs_cum_sum(i-1)+ |
150 |
|
|
& cg3d_dofs_process(i-1) |
151 |
|
|
ENDIF |
152 |
|
|
ENDDO |
153 |
|
|
|
154 |
|
|
#else /* ALLOW_USE_MPI */ |
155 |
|
|
|
156 |
|
|
cg3d_dofs_process (0) = INT(DoFCountColor(1))+1 |
157 |
|
|
cg3d_dofs_cum_sum (0) = INT(DoFCountColor(1))+1 |
158 |
|
|
|
159 |
|
|
#endif /* ALLOW_USE_MPI */ |
160 |
|
|
|
161 |
|
|
DO bj = myByLo(myThid), myByHi(myThid) |
162 |
|
|
DO bi = myBxLo(myThid), myBxHi(myThid) |
163 |
|
|
DO j=1,sNy |
164 |
|
|
DO i=1,sNx |
165 |
|
|
DO k=1,Nr |
166 |
|
|
IF (cg3d_petsc_dofs(i,j,k,bi,bj).ge.0 ) THEN |
167 |
|
|
color = cg3d_petsc_color (i,j,k,bi,bj) |
168 |
|
|
rank = cg3d_color_rank (color) |
169 |
|
|
cg3d_petsc_dofs(i,j,k,bi,bj) = |
170 |
|
|
& cg3d_petsc_dofs(i,j,k,bi,bj) + |
171 |
|
|
& cg3d_dofs_cum_sum(rank) |
172 |
|
|
ENDIF |
173 |
|
|
ENDDO |
174 |
|
|
ENDDO |
175 |
|
|
ENDDO |
176 |
|
|
ENDDO |
177 |
|
|
ENDDO |
178 |
|
|
|
179 |
|
|
_EXCH_XYZ_RS(cg3d_petsc_dofs,myThid) |
180 |
|
|
|
181 |
dgoldberg |
1.2 |
call write_fld_xyz_rs ('petscDofs1','',cg3d_petsc_dofs,0,mythid) |
182 |
|
|
call write_fld_xyz_rs ('petscColor1','',cg3d_petsc_color,0,mythid) |
183 |
|
|
|
184 |
dgoldberg |
1.1 |
|
185 |
|
|
#endif /* ALLOW_PETSC */ |
186 |
|
|
|
187 |
|
|
|
188 |
|
|
#endif |
189 |
|
|
RETURN |
190 |
|
|
END |