OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
i23cor3.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!|| i23cor3 ../engine/source/interfaces/int23/i23cor3.F
25!||--- called by ------------------------------------------------------
26!|| i23mainf ../engine/source/interfaces/int23/i23mainf.F
27!||--- uses -----------------------------------------------------
28!|| tri7box ../engine/share/modules/tri7box.F
29!||====================================================================
30 SUBROUTINE i23cor3(JLT ,NIN ,X ,IRECT ,NSN ,
31 2 NSV ,CAND_E ,CAND_N ,STF ,STFN ,
32 3 MSR ,MS ,V ,XI ,YI ,
33 4 ZI ,IX1 ,IX2 ,IX3 ,IX4 ,
34 5 NSVG ,IGSTI ,STIF ,KMIN ,KMAX ,
35 6 IGAP ,GAP ,GAP_S ,GAPV ,GAPMAX,
36 7 GAPMIN,GAP_M ,VXI ,VYI ,VZI ,
37 8 MSI ,NODNX_SMS,NSMS ,KINET ,X1 ,
38 9 Y1 ,Z1 ,X2 ,Y2 ,Z2 ,
39 A X3 ,Y3 ,Z3 ,X4 ,Y4 ,
40 B Z4 ,NX1 ,NX2 ,NX3 ,NX4 ,
41 C NY1 ,NY2 ,NY3 ,NY4 ,NZ1 ,
42 D NZ2 ,NZ3 ,NZ4 ,KINI ,INDEX )
43C-----------------------------------------------
44C M o d u l e s
45C-----------------------------------------------
46 USE tri7box
47C-----------------------------------------------
48C I m p l i c i t T y p e s
49C-----------------------------------------------
50#include "implicit_f.inc"
51C-----------------------------------------------
52C G l o b a l P a r a m e t e r s
53C-----------------------------------------------
54#include "mvsiz_p.inc"
55C-----------------------------------------------
56C C o m m o n B l o c k s
57C-----------------------------------------------
58#include "sms_c.inc"
59C-----------------------------------------------
60C D u m m y A r g u m e n t s
61C-----------------------------------------------
62 INTEGER IRECT(4,*), NSV(*), CAND_E(*), CAND_N(*),KINET(*),KINI(*),
63 . MSR(*), NODNX_SMS(*), INDEX(*),
64 . JLT, NOINT, IGAP , NSN, NIN, IGSTI
65 INTEGER IX1(MVSIZ), IX2(MVSIZ), IX3(MVSIZ), IX4(MVSIZ),
66 . NSVG(MVSIZ), NSMS(MVSIZ)
67C REAL
68 my_real
69 . X(3,*), STF(*), STFN(*), GAP_S(*), GAP_M(*),
70 . MS(*), V(3,*),
71 . GAP, KMIN, KMAX, GAPMAX, GAPMIN
72C REAL
73 my_real
74 . x1(mvsiz), x2(mvsiz), x3(mvsiz), x4(mvsiz),
75 . y1(mvsiz), y2(mvsiz), y3(mvsiz), y4(mvsiz),
76 . z1(mvsiz), z2(mvsiz), z3(mvsiz), z4(mvsiz),
77 . xi(mvsiz), yi(mvsiz), zi(mvsiz),
78 . nx1(mvsiz), nx2(mvsiz), nx3(mvsiz), nx4(mvsiz),
79 . ny1(mvsiz), ny2(mvsiz), ny3(mvsiz), ny4(mvsiz),
80 . nz1(mvsiz), nz2(mvsiz), nz3(mvsiz), nz4(mvsiz),
81 . pene(mvsiz),stif(mvsiz) ,gapv(mvsiz),
82 . vxi(mvsiz), vyi(mvsiz), vzi(mvsiz), msi(mvsiz)
83C-----------------------------------------------
84C L o c a l V a r i a b l e s
85C-----------------------------------------------
86 INTEGER I ,J ,IL, L, IG, ITMP, NN, NI
87C-----------------------------------------------
88 IF(IGAP==0)then
89 DO i=1,jlt
90 gapv(i)=gap
91 ENDDO
92 ELSE
93 DO i=1,jlt
94 IF(cand_n(i)<=nsn) THEN
95 gapv(i)=gap_s(cand_n(i))+gap_m(cand_e(i))
96 ELSE
97 gapv(i)=gapfi(nin)%P(cand_n(i)-nsn)+gap_m(cand_e(i))
98 ENDIF
99 gapv(i)=min(gapv(i),gapmax)
100 gapv(i)=max(gapmin,gapv(i))
101 END DO
102 ENDIF
103C
104 DO i=1,jlt
105 ni = cand_n(i)
106 IF(ni<=nsn)THEN
107 ig = nsv(ni)
108 nsvg(i) = ig
109C Kini is not used in TYPE23
110 kini(i) = kinet(ig)
111 xi(i) = x(1,ig)
112 yi(i) = x(2,ig)
113 zi(i) = x(3,ig)
114 vxi(i) = v(1,ig)
115 vyi(i) = v(2,ig)
116 vzi(i) = v(3,ig)
117 msi(i)= ms(ig)
118 ELSE
119 nn = ni - nsn
120 nsvg(i) = -nn
121 kini(i) = kinfi(nin)%P(nn)
122 xi(i) = xfi(nin)%P(1,nn)
123 yi(i) = xfi(nin)%P(2,nn)
124 zi(i) = xfi(nin)%P(3,nn)
125 vxi(i)= vfi(nin)%P(1,nn)
126 vyi(i)= vfi(nin)%P(2,nn)
127 vzi(i)= vfi(nin)%P(3,nn)
128 msi(i)= msfi(nin)%P(nn)
129 END IF
130 END DO
131C
132 DO i=1,jlt
133 l=cand_e(i)
134C
135 ix1(i)=irect(1,l)
136 ix2(i)=irect(2,l)
137 ix3(i)=irect(3,l)
138 ix4(i)=irect(4,l)
139 END DO
140C
141 DO i=1,jlt
142 l=cand_e(i)
143C
144 x1(i)=x(1,ix1(i))
145 y1(i)=x(2,ix1(i))
146 z1(i)=x(3,ix1(i))
147C
148 x2(i)=x(1,ix2(i))
149 y2(i)=x(2,ix2(i))
150 z2(i)=x(3,ix2(i))
151C
152 x3(i)=x(1,ix3(i))
153 y3(i)=x(2,ix3(i))
154 z3(i)=x(3,ix3(i))
155C
156 x4(i)=x(1,ix4(i))
157 y4(i)=x(2,ix4(i))
158 z4(i)=x(3,ix4(i))
159C
160 END DO
161C
162 DO i=1,jlt
163 l = cand_e(i)
164 ni = cand_n(i)
165 IF(ni<=nsn)THEN
166 stif(i)=stf(l)*abs(stfn(ni))
167 ELSE
168 nn = ni - nsn
169 stif(i)=stf(l)*abs(stifi(nin)%P(nn))
170 END IF
171 ENDDO
172C
173 IF(idtmins==2)THEN
174 DO i=1,jlt
175 IF(nsvg(i)>0)THEN
176 nsms(i)=nodnx_sms(nsvg(i))
177 . +nodnx_sms(ix1(i))+nodnx_sms(ix2(i))
178 . +nodnx_sms(ix3(i))+nodnx_sms(ix4(i))
179 ELSE
180 nn=-nsvg(i)
181 nsms(i)=nodnxfi(nin)%P(nn)
182 . +nodnx_sms(ix1(i))+nodnx_sms(ix2(i))
183 . +nodnx_sms(ix3(i))+nodnx_sms(ix4(i))
184 END IF
185 ENDDO
186 IF(idtmins_int/=0)THEN
187 DO i=1,jlt
188 IF(nsms(i)==0)nsms(i)=-1
189 ENDDO
190 END IF
191 ELSEIF(idtmins_int/=0)THEN
192 DO i=1,jlt
193 nsms(i)=-1
194 ENDDO
195 ENDIF
196C
197 RETURN
198 END
199
subroutine i23cor3(jlt, nin, x, irect, nsn, nsv, cand_e, cand_n, stf, stfn, msr, ms, v, xi, yi, zi, ix1, ix2, ix3, ix4, nsvg, igsti, stif, kmin, kmax, igap, gap, gap_s, gapv, gapmax, gapmin, gap_m, vxi, vyi, vzi, msi, nodnx_sms, nsms, kinet, x1, y1, z1, x2, y2, z2, x3, y3, z3, x4, y4, z4, nx1, nx2, nx3, nx4, ny1, ny2, ny3, ny4, nz1, nz2, nz3, nz4, kini, index)
Definition i23cor3.F:43
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21
type(real_pointer2), dimension(:), allocatable vfi
Definition tri7box.F:459
type(real_pointer), dimension(:), allocatable stifi
Definition tri7box.F:449
type(real_pointer), dimension(:), allocatable gapfi
Definition tri7box.F:449
type(int_pointer), dimension(:), allocatable nodnxfi
Definition tri7box.F:440
type(real_pointer), dimension(:), allocatable msfi
Definition tri7box.F:449
type(real_pointer2), dimension(:), allocatable xfi
Definition tri7box.F:459
type(int_pointer), dimension(:), allocatable kinfi
Definition tri7box.F:440