OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
cdk6inx.F
Go to the documentation of this file.
1Copyright> OpenRadioss
2Copyright> Copyright (C) 1986-2025 Altair Engineering Inc.
3Copyright>
4Copyright> This program is free software: you can redistribute it and/or modify
5Copyright> it under the terms of the GNU Affero General Public License as published by
6Copyright> the Free Software Foundation, either version 3 of the License, or
7Copyright> (at your option) any later version.
8Copyright>
9Copyright> This program is distributed in the hope that it will be useful,
10Copyright> but WITHOUT ANY WARRANTY; without even the implied warranty of
11Copyright> MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12Copyright> GNU Affero General Public License for more details.
13Copyright>
14Copyright> You should have received a copy of the GNU Affero General Public License
15Copyright> along with this program. If not, see <https://www.gnu.org/licenses/>.
16Copyright>
17Copyright>
18Copyright> Commercial Alternative: Altair Radioss Software
19Copyright>
20Copyright> As an alternative to this open-source version, Altair also offers Altair Radioss
21Copyright> software under a commercial license. Contact Altair to discuss further if the
22Copyright> commercial version may interest you: https://www.altair.com/radioss/.
23C
24!||====================================================================
25!|| cdk6inx ../starter/source/elements/sh3n/coquedk6/cdk6inx.F
26!||--- called by ------------------------------------------------------
27!|| lectur ../starter/source/starter/lectur.F
28!||--- calls -----------------------------------------------------
29!|| ancmsg ../starter/source/output/message/message.F
30!||--- uses -----------------------------------------------------
31!|| message_mod ../starter/share/message_module/message_mod.F
32!||====================================================================
33 SUBROUTINE cdk6inx(IXTG,IXTG1,ICNOD)
34 USE message_mod
35C--------------------------------------------------------
36C Construction les connectivites sup DES ELEMENTS COQUES TRIANGULAIRE
37C--------------------------------------------------------
38C-----------------------------------------------
39C I m p l i c i t T y p e s
40C-----------------------------------------------
41#include "implicit_f.inc"
42C-----------------------------------------------
43C C o m m o n B l o c k s
44C-----------------------------------------------
45#include "com04_c.inc"
46C-----------------------------------------------
47C V a r i a b l e s
48C-----------------------------------------------
49 INTEGER IXTG(NIXTG,*),IXTG1(4,*),ICNOD(*)
50C-----------------------------------------------
51C L o c a l V a r i a b l e s
52C-----------------------------------------------
53 INTEGER I, J, NEL1,N1,N2,N3,NJ1,NJ2,NJ3,IMIN,IMAX,JMIN,JMAX,
54 . II,JJ
55C-----------------------------------------------
56C
57 nel1=0
58 DO i=1,numeltg
59 IF (icnod(i)==6) THEN
60 nel1 = nel1+1
61 ixtg1(1,nel1) = 0
62 ixtg1(2,nel1) = 0
63 ixtg1(3,nel1) = 0
64 ixtg1(4,nel1) = i
65 ENDIF
66 ENDDO
67 IF (nel1/=numeltg6) THEN
68 CALL ancmsg(msgid=364,
69 * anmode=anstop,
70 * msgtype=msgerror,c1='S3N6')
71 ENDIF
72C
73 DO i=1,numeltg6
74 IF (ixtg1(1,i)==0.OR.ixtg1(2,i)==0
75 . .OR.ixtg1(3,i)==0) THEN
76 ii=ixtg1(4,i)
77 n1= ixtg(2,ii)
78 n2= ixtg(3,ii)
79 n3= ixtg(4,ii)
80C IMIN= MIN(N1,N2,N3)
81C IMAX= MAX(N1,N2,N3)
82 DO j =i+1,numeltg6
83 jj=ixtg1(4,j)
84 nj1= ixtg(2,jj)
85 nj2= ixtg(3,jj)
86 nj3= ixtg(4,jj)
87C JMIN= MIN(NJ1,NJ2,NJ3)
88C JMAX= MAX(NJ1,NJ2,NJ3)
89C--------- ligne 1----------
90 IF (ixtg1(1,i)==0) THEN
91 IF ((n1+n2)==(nj1+nj2)) THEN
92 IF (abs(n1-n2)==abs(nj1-nj2)) THEN
93 ixtg1(1,i) = nj3
94 ixtg1(1,j) = n3
95 ENDIF
96 ELSEIF ((n1+n2)==(nj2+nj3)) THEN
97 IF (abs(n1-n2)==abs(nj2-nj3)) THEN
98 ixtg1(1,i) = nj1
99 ixtg1(2,j) = n3
100 ENDIF
101 ELSEIF ((n1+n2)==(nj3+nj1)) THEN
102 IF (abs(n1-n2)==abs(nj3-nj1)) THEN
103 ixtg1(1,i) = nj2
104 ixtg1(3,j) = n3
105 ENDIF
106 ENDIF
107 ENDIF
108C--------- ligne 2----------
109 IF (ixtg1(2,i)==0) THEN
110 IF ((n2+n3)==(nj1+nj2)) THEN
111 IF (abs(n2-n3)==abs(nj1-nj2)) THEN
112 ixtg1(2,i) = nj3
113 ixtg1(1,j) = n1
114 ENDIF
115 ELSEIF ((n2+n3)==(nj2+nj3)) THEN
116 IF (abs(n2-n3)==abs(nj2-nj3)) THEN
117 ixtg1(2,i) = nj1
118 ixtg1(2,j) = n1
119 ENDIF
120 ELSEIF ((n2+n3)==(nj3+nj1)) THEN
121 IF (abs(n2-n3)==abs(nj3-nj1)) THEN
122 ixtg1(2,i) = nj2
123 ixtg1(3,j) = n1
124 ENDIF
125 ENDIF
126 ENDIF
127C--------- ligne 3----------
128 IF (ixtg1(3,i)==0) THEN
129 IF ((n1+n3)==(nj1+nj2)) THEN
130 IF (abs(n1-n3)==abs(nj1-nj2)) THEN
131 ixtg1(3,i) = nj3
132 ixtg1(1,j) = n2
133 ENDIF
134 ELSEIF ((n1+n3)==(nj2+nj3)) THEN
135 IF (abs(n1-n3)==abs(nj2-nj3)) THEN
136 ixtg1(3,i) = nj1
137 ixtg1(2,j) = n2
138 ENDIF
139 ELSEIF ((n1+n3)==(nj3+nj1)) THEN
140 IF (abs(n1-n3)==abs(nj3-nj1)) THEN
141 ixtg1(3,i) = nj2
142 ixtg1(3,j) = n2
143 ENDIF
144 ENDIF
145 ENDIF
146 ENDDO
147C write(*,*)I,IXTG1(1,I),IXTG1(2,I),IXTG1(3,I)
148 ENDIF
149 ENDDO
150 RETURN
151 END
subroutine cdk6inx(ixtg, ixtg1, icnod)
Definition cdk6inx.F:34
subroutine ancmsg(msgid, msgtype, anmode, i1, i2, i3, i4, i5, i6, i7, i8, i9, i10, i11, i12, i13, i14, i15, i16, i17, i18, i19, i20, r1, r2, r3, r4, r5, r6, r7, r8, r9, c1, c2, c3, c4, c5, c6, c7, c8, c9, prmode)
Definition message.F:889