OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
ssort_n4.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/.
23!||====================================================================
24!|| ssort_n4 ../engine/source/elements/solid/solide/ssort_n4.F
25!||--- called by ------------------------------------------------------
26!|| sfor_n2s4 ../engine/source/elements/solid/solide/sfor_n2s4.F
27!||====================================================================
28 SUBROUTINE ssort_n4(XI, YI, ZI , MARGE,
29 . X1, X2, X3, X4,
30 . Y1, Y2, Y3, Y4,
31 . Z1, Z2, Z3, Z4,
32 . IFC1, STIF, NEL)
33C-----------------------------------------------
34C I m p l i c i t T y p e s
35C-----------------------------------------------
36#include "implicit_f.inc"
37C-----------------------------------------------
38C G l o b a l P a r a m e t e r s
39C-----------------------------------------------
40#include "mvsiz_p.inc"
41C-----------------------------------------------
42C D u m m y A r g u m e n t s
43C-----------------------------------------------
44 INTEGER, INTENT (IN) :: NEL
45 INTEGER, DIMENSION(MVSIZ),INTENT (INOUT) :: IFC1
46 my_real, DIMENSION(MVSIZ), INTENT (IN) :: MARGE,
47 . XI, YI, ZI,STIF,
48 . x1, x2, x3, x4,
49 . y1, y2, y3, y4,
50 . z1, z2, z3, z4
51C-----------------------------------------------
52C C o m m o n B l o c k s
53C-----------------------------------------------
54C-----------------------------------------------
55C L o c a l V a r i a b l e s
56C-----------------------------------------------
57 INTEGER I,J,K
58C 12
59 my_real
60 . RX, RY, RZ, SX, SY, SZ,NX,NY,NZ,BBB,
61 . dx,dy,dz,dd,pene(mvsiz),norm,dmin,dmin1
62C----------------------------
63 DO i=1,nel
64 IF (ifc1(i)>0) cycle
65 rx =x2(i)+x3(i)-x1(i)-x4(i)
66 ry =y2(i)+y3(i)-y1(i)-y4(i)
67 rz =z2(i)+z3(i)-z1(i)-z4(i)
68 sx =x3(i)+x4(i)-x1(i)-x2(i)
69 sy =y3(i)+y4(i)-y1(i)-y2(i)
70 sz =z3(i)+z4(i)-z1(i)-z2(i)
71 nx =ry*sz - rz*sy
72 ny =rz*sx - rx*sz
73 nz =rx*sy - ry*sx
74 norm=one/max(em20,sqrt(nx*nx+ny*ny+nz*nz))
75 bbb = ((x3(i)-xi(i))*nx + (y3(i)-yi(i))*ny +
76 . (z3(i)-zi(i))*nz)*norm
77 pene(i) = abs(bbb)
78 IF (pene(i)<marge(i).AND.stif(i)>zero) ifc1(i)=2
79 ENDDO
80C-------if degenerated quad not possible have 1=3 or 2=4
81#include "vectorize.inc"
82 DO i=1,nel
83 IF (ifc1(i)==0) cycle
84 dx =x4(i)-x3(i)
85 dy =y4(i)-y3(i)
86 dz =z4(i)-z3(i)
87 dmin = abs(dx)+abs(dy)+abs(dz)
88 IF (dmin==zero) THEN
89 ifc1(i)=3
90 dx =x2(i)-x1(i)
91 dy =y2(i)-y1(i)
92 dz =z2(i)-z1(i)
93 dmin1 = abs(dx)+abs(dy)+abs(dz)
94 IF (dmin1==zero) ifc1(i)=0
95 cycle
96 END IF
97 dx =x2(i)-x1(i)
98 dy =y2(i)-y1(i)
99 dz =z2(i)-z1(i)
100 dmin = abs(dx)+abs(dy)+abs(dz)
101 IF (dmin==zero) THEN
102 ifc1(i)=6
103 cycle
104 END IF
105 dx =x4(i)-x1(i)
106 dy =y4(i)-y1(i)
107 dz =z4(i)-z1(i)
108 dmin = abs(dx)+abs(dy)+abs(dz)
109 IF (dmin==zero) THEN
110 ifc1(i)=4
111 dx =x3(i)-x2(i)
112 dy =y3(i)-y2(i)
113 dz =z3(i)-z2(i)
114 dmin1 = abs(dx)+abs(dy)+abs(dz)
115 IF (dmin1==zero) ifc1(i)=0
116 cycle
117 END IF
118 dx =x3(i)-x2(i)
119 dy =y3(i)-y2(i)
120 dz =z3(i)-z2(i)
121 dmin = abs(dx)+abs(dy)+abs(dz)
122 IF (dmin==zero) THEN
123 ifc1(i)=5
124 cycle
125 END IF
126 ENDDO
127C
128 RETURN
129 END
norm(diag(diag(diag(inv(mat))) -id.SOL), 2) % destroy mumps instance id.JOB
#define max(a, b)
Definition macros.h:21
subroutine ssort_n4(xi, yi, zi, marge, x1, x2, x3, x4, y1, y2, y3, y4, z1, z2, z3, z4, ifc1, stif, nel)
Definition ssort_n4.F:33