Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
KtInitCRS.f90
Go to the documentation of this file.
1 
2 !!****
3 !!
4 !! NAME
5 !! KtNumNnz
6 !!
7 !! FUNCTION
8 !! This subroutine uses the node numbering combined with
9 !! the connectivity table in order to calculate the number
10 !! of nonzero entries in the stiffness matrix due only to
11 !! the elements and nodes on this processor.
12 !!
13 !! INPUTS
14 !! NumNp -- Total number of nodes that this proc knows about
15 !! NumEl -- Total number of elements that this proc knows about
16 !! ElConnVol -- Connectivity table
17 !!
18 !! OUTPUTS
19 !! nnz -- The number of nonzeros in the K matrix
20 !!
21 !! USES
22 !! none
23 !!
24 !!****
25 
26 SUBROUTINE ktnumnnz(NumNp,NumEl,ElConnVol,nnz)
27 
28  USE precision
29  USE implicit_global
30 
31  IMPLICIT NONE
32 
33  ! ... Input variables
34  INTEGER :: numnp, numel
35  INTEGER :: elconnvol(1:8,1:numel)
36 
37  ! ... Output variables
38  INTEGER :: nnz
39 
40  ! ... local variables
41  INTEGER :: i, j, k, m, n, counter
42  INTEGER :: innz(1:56), jnnz(1:26)
43 
44 
45 !
46 ! Count the nonzeros that should be in the K matrix
47 !
48 
49  ! Loop through nodes counting off-diagonal blocks of nonzeros
50  nnz = 0
51  DO i = 1, numnp
52 
53  ! Initialize connectivity variables
54  innz(:) = -1
55  jnnz(:) = -1
56 
57  ! ... Construct nodal connectivity vector
58  ! ... there are a maximum of 8 elements with node i
59  ! ... innz caries the nodes of the elements associated with node i
60  DO j = 1, numel
61  DO k = 1, 8
62  IF (elconnvol(k,j) == i) THEN
63  DO m = 1, 8
64  IF (k /= m) THEN
65  DO n = 1, 56
66  IF (innz(n) == -1) THEN
67  innz(n) = elconnvol(m,j)
68  EXIT
69  ENDIF
70  ENDDO
71  ENDIF
72  ENDDO
73  ENDIF
74  ENDDO
75  ENDDO
76 
77  ! ...Eliminate duplicates from nodal connectivity vector
78  ! ... Of the 56 in innz, 3 * 12 - 6 are duplicates, (30)
79  ! ... jnnz caries the unique entries
80  DO j = 1, 56
81  IF (innz(j) /= -1) THEN
82  DO k = 1, 26
83  IF (jnnz(k) /= -1) THEN
84  IF (jnnz(k) == innz(j)) THEN
85  EXIT
86  ENDIF
87  ELSE
88  jnnz(k) = innz(j)
89 
90  ! ... the number of non-zeros is incremented each time
91  ! ... a unique entry is found in innz
92  nnz = nnz + 1
93  EXIT
94  ENDIF
95  ENDDO
96  ENDIF
97  ENDDO
98  ENDDO
99 
100  ! ... Take into account the blocks on the diagonal
101  ! ... these were the nodes that were looped over above
102  ! ... and not added to the connectivity vectors
103  nnz = nnz + numnp
104 
105  ! ... Convert number of blocks to number of nonzeros
106  ! ... three nodes corresponds to a 3x3 stiffness matrix
107  ! ... multiplied by (1) because of 1 degree of freedom
108  ! nnz = (1)*nnz
109 
110 
111 END SUBROUTINE ktnumnnz
112 
113 
114 
115 
116 !!****
117 !!
118 !! NAME
119 !! KtInitCRS
120 !!
121 !! FUNCTION
122 !! This subroutine uses the node numbering combined with
123 !! the connectivity table and number of nonzeros in the K
124 !! matrix to assemble the pre-allocated compressed row
125 !! storage arrays. It does this by putting a definite
126 !! (not assumed) zero at each point that can contain a
127 !! nonzero value. The actual values in the K matrix are
128 !! added in the LocThermCap_v3d8 subroutine.
129 !!
130 !! INPUTS
131 !! NumNp -- Total number of nodes that this proc knows about
132 !! NumEl -- Total number of elements that this proc knows about
133 !! ElConnVol -- Connectivity table
134 !! nnz -- The number of nonzeros in the K matrix
135 !!
136 !! OUTPUTS
137 !! rp -- The row mapping vector
138 !! cval -- The collumn mapping vector
139 !! aval -- The value vector (which will be returned as all zeros)
140 !!
141 !! USES
142 !! none
143 !!
144 !!****
145 
146 SUBROUTINE ktinitcrs(NumNp,NumEl,ElConnVol,nnz,rp,cval,aval)
147 
148 
149  USE precision
150  USE implicit_global
151 
152  IMPLICIT NONE
153 
154  include 'mpif.h'
155 
156  ! ... Input variables
157  INTEGER :: numnp, numel
158  INTEGER :: elconnvol(1:8,1:numel)
159  INTEGER :: nnz
160 
161  ! ... Output variables
162  INTEGER :: rp(1:gnumnp+1)
163  INTEGER :: cval(1:nnz)
164  INTEGER :: aval(1:nnz)
165 
166  ! ... local variables
167  INTEGER :: i, j, k, m, n, counter, ii
168  INTEGER :: innz(1:56), jnnz(1:27)
169 
170 
171  ! ... Initialize CRS variables
172  aval(:) = 0.0
173  cval(:) = -1
174  rp(:) = -1
175  rp(1) = 0
176 
177  ! ... Loop through nodes
178  counter = 0
179  DO i = 1, gnumnp
180 
181  ! ... If this node is on this processor
182  IF (global2local(i) /= -1) THEN
183 
184  ii = global2local(i)
185 
186  ! ... Initialize connectivity variables
187  innz(:) = -1
188  jnnz(:) = -1
189 
190  ! ... Make sure diagonal terms are included
191  jnnz(27) = ii
192 
193  ! ... Construct nodal connectivity vector
194  ! ... there are a maximum of 8 elements that contain node ii
195  ! ... innz caries the nodes of the elements associated with node ii
196  DO j = 1, numel
197  DO k = 1, 8
198  ! ... Find the element and element local node number corresponding
199  ! ... to process local node number ii. This is identified by
200  ! ... integer k.
201  IF (elconnvol(k,j) == ii) THEN
202  DO m = 1, 8
203  ! ... Find other 7 nodes (m) in element j.
204  IF (k /= m) THEN
205  DO n = 1, 56
206  ! ... Store the process local nodes belonging to element j in
207  ! ... the vector innz. There are a maximum of 56 nodes that
208  ! ... can belong to the same elements as node ii.
209  ! ... (8 elements) X (7 non-ii nodes per element) = 56 nodes
210  IF (innz(n) == -1) THEN
211  innz(n) = elconnvol(m,j)
212  EXIT
213  ENDIF
214  ENDDO
215  ENDIF
216  ENDDO
217  ENDIF
218  ENDDO
219  ENDDO
220 
221 
222  ! ...Eliminate duplicates from nodal connectivity vector
223  ! ... Of the 56 in innz, 3 * 12 - 6 are duplicates, (30)
224  ! ... jnnz caries the 26 unique entries + 1 for the diagonal (ii)
225  ! ... which is not counted
226  DO j = 1, 56
227  ! ... Look though the 56 entries in innz for a non -1.
228  IF (innz(j) /= -1) THEN
229  ! ... If so, look through the 27-1 entries in jnnz for a non -1.
230  DO k = 1, 26
231  IF (jnnz(k) /= -1) THEN
232  IF (jnnz(k) == innz(j)) THEN
233  ! ... If the local node number found in innz already recorded
234  ! ... in jnnz, then skip it.
235  EXIT
236  ENDIF
237  ELSE
238  ! ... If the local node number is not already recorded in jnnz
239  ! ... then enter it into jnnz.
240  jnnz(k) = innz(j)
241  EXIT
242  ENDIF
243  ENDDO
244  ENDIF
245  ENDDO
246 
247  ! ... Loop through rows with same nonzero blocks
248 
249  ! ... To construct cval, find the column value of a global node that
250  ! ... is equal to the node stored in jnnz.
251  DO n = 1, gnumnp
252  DO k = 1, 27
253  IF(jnnz(k) /= -1) THEN
254  ! ... Check to see that global node n is the same node as local node jnnz(k)=m.
255  ! ... If so, then enter the node column number in the next entry of cval.
256  m = local2global(jnnz(k))
257  IF (m == n) THEN
258  counter = counter + 1
259  ! ... using C convention, column n is n - 1
260  cval(counter) = m - 1
261  ENDIF
262  ENDIF
263  ENDDO
264  ENDDO
265 
266  ! ... Construct rp, this value corresponding to the index number
267  ! ... counter + 1 in C convention.
268  rp(i+1) = counter
269 
270 
271  ! ... If this node is not on this processor. My guess, this is just a place holder ... COstoich.
272  ELSE
273 
274  rp(i+1) = rp(i)
275 
276  ENDIF
277 
278 
279 
280  ENDDO
281 
282 
283 END SUBROUTINE ktinitcrs
FT m(int i, int j) const
j indices k indices k
Definition: Indexing.h:6
subroutine ktnumnnz(NumNp, NumEl, ElConnVol, nnz)
Definition: KtInitCRS.f90:26
subroutine ktinitcrs(NumNp, NumEl, ElConnVol, nnz, rp, cval, aval)
Definition: KtInitCRS.f90:146
blockLoc i
Definition: read.cpp:79
const NT & n
j indices j
Definition: Indexing.h:6