-
Notifications
You must be signed in to change notification settings - Fork 8
/
Copy pathedgesInitialize.f90
133 lines (108 loc) · 3.75 KB
/
edgesInitialize.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
!> @file edgesInitialize.f90
!!
!! Generation of temporary edge lists.
!
! *****************************************************************************
!
! (c) J. Blazek, CFD Consulting & Analysis, www.cfd-ca.de
! Created February 25, 2014
! Last modification: May 21, 2014
!
! *****************************************************************************
!
! This program is free software; you can redistribute it and/or
! modify it under the terms of the GNU General Public License
! as published by the Free Software Foundation; either version 2
! of the License, or (at your option) any later version.
!
! This program is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with this program; if not, write to the Free Software
! Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
!
! *****************************************************************************
!> Generates temporary lists with nodes of an edge (niedge, iedge).
!! Computes total number of edges (interior + dummy). The edge lists
!! are used in the subroutines EdgesFinalize and InitMetrics.
!!
!! @param niedge pointer from a node to iedge()
!! @param iedge linked list of edge endpoints:
!! @li (1,*) = point j of edge (i,j)
!! @li (2,*) = next point j which is also connected to i;
!! if <0 - no further connections
!! @li (3,*) = pointer to edge() - used in InitMetrics to associate
!! face vector sij() with the correct edge
!!
subroutine EdgesInitialize( niedge,iedge )
use ModGeometry
use ModNumerics
use ModInterfaces, only : ErrorMessage
implicit none
! parameters
integer, intent(out) :: niedge(:), iedge(:,:)
! local variables
integer :: d, cedge, cedge2, mxedges
integer :: i, j, ic, ie, n
! *****************************************************************************
mxedges = ubound(iedge,2) ! max. possible number of edges
! reset all pointers
do i=1,nndint
niedge(i) = -777
enddo
do ie=1,mxedges
iedge(1,ie) = -777
iedge(2,ie) = -777
iedge(3,ie) = -777
enddo
! loop over nodes of all triangles
nedint = 0
do n=1,3
! - loop over triangles
do ic=1,ntria
i = tria(n,ic)
if (n < 3) then
j = tria(n+1,ic)
else
j = tria(1,ic)
endif
if (i > j) then ! lower index first
d = i
i = j
j = d
endif
if (niedge(i) < 0) then
! ----- define new edge
nedint = nedint + 1
if (nedint > mxedges) then
call ErrorMessage( "max. number of edges reached" )
endif
niedge(i) = nedint
iedge(1,nedint) = j
else
! ----- insert node "j" into list of adjacent nodes
cedge = niedge(i)
10 continue
if (iedge(1,cedge) == j) goto 20
cedge2 = iedge(2,cedge)
if (cedge2 < 0) then
nedint = nedint + 1
if (nedint > mxedges) then
call ErrorMessage( "max. number of edges reached" )
endif
iedge(2,cedge ) = nedint
iedge(1,nedint) = j
goto 20
endif
cedge = cedge2
goto 10
20 continue
endif
enddo ! loop over triangles
enddo ! loop over nodes of triangles
! set total no. of edges (add edges to dummy nodes)
nedges = nedint + (nnodes-nndint)
end subroutine EdgesInitialize