OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
i25pwr3.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!|| i25pwr3 ../starter/source/interfaces/inter3d1/i25pwr3.F
25!||--- called by ------------------------------------------------------
26!|| inint3 ../starter/source/interfaces/inter3d1/inint3.F
27!||--- calls -----------------------------------------------------
28!|| ancmsg ../starter/source/output/message/message.F
29!||--- uses -----------------------------------------------------
30!|| message_mod ../starter/share/message_module/message_mod.F
31!||====================================================================
32 SUBROUTINE i25pwr3(ITAB ,INACTI,CAND_E,CAND_N ,STFN ,
33 1 X ,I_STOK,NSV ,IWPENE ,PENE_OLD,
34 2 NOINT ,NTY ,MSR ,IRTLM ,IRECT ,
35 4 NSN ,ID ,TITR ,MSEGLO,ICONT_I)
36 USE message_mod
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 "scr03_c.inc"
46#include "units_c.inc"
47C-----------------------------------------------
48C D u m m y A r g u m e n t s
49C-----------------------------------------------
50 INTEGER ITAB(*),CAND_E(*),CAND_N(*), IRECT(4,*), IRTLM(4,*),
51 . MSEGLO(*)
52 INTEGER I_STOK,NSV(*),MSR(*),IWPENE,INACTI,NOINT,NTY,NSN
53 INTEGER , INTENT(OUT) :: ICONT_I(NSN)
54C REAL
56 . stfn(*),x(3,*),pene_old(5,*)
57 INTEGER ID
58 CHARACTER(LEN=NCHARTITLE) :: TITR
59C-----------------------------------------------
60C L o c a l V a r i a b l e s
61C-----------------------------------------------
62 INTEGER I, J, L
63 INTEGER IX1, IX2, IX3, IX4, NSVG
64C REAL
65C-----------------------------------------------
66 DO 100 i=1,i_stok
67 j=cand_n(i)
68 l=cand_e(i)
69
70
71 IF(irtlm(1,j)==mseglo(cand_e(i)))THEN
72
73 ix1=irect(1,l)
74 ix2=irect(2,l)
75 ix3=irect(3,l)
76 ix4=irect(4,l)
77 nsvg=nsv(j)
78
79C
80 IF(pene_old(5,j)/=zero)THEN
81C True initial penetration
82 iwpene=iwpene+1
83
84 IF(ipri>=5 )
85 . CALL ancmsg(msgid=1164,
86 . msgtype=msgwarning,
87 . anmode=aninfo_blind_1,
88 . i1=itab(nsvg),
89 . i2=itab(ix1),
90 . i3=itab(ix2),
91 . i4=itab(ix3),
92 . i5=itab(ix4),
93 . r1=pene_old(5,j),
94 . prmod=msg_cumu)
95 IF(inacti==0)THEN
96C Ignore initial penetrations
97 icont_i(j)=-irtlm(1,j)
98 irtlm(1,j) = 0
99 irtlm(2,j) = 0
100 irtlm(3,j) = 0
101 pene_old(5,j)= zero
102 ELSEIF(inacti==1) THEN
103C DESACTIVATION DES NOEUDS
104 WRITE(iout,'(A)')'NODE STIFFNESS IS SET TO ZERO'
105 stfn(j) = zero
106 icont_i(j)=-irtlm(1,j)
107C ELSE IF(INACTI==2) THEN
108C DESACTIVATION DES ELEMENTS
109C WRITE(IOUT,'(A)')
110C . 'INACTI=2 IS NOT AVAILABLE FOR INTERFACE TYPE25'
111C ELSE IF(INACTI==3) THEN
112C CHANGE LES COORDONNEES DES NOEUDS SECND
113C WRITE(IOUT,'(A)')
114C . 'INACTI=3 IS NOT AVAILABLE FOR INTERFACE TYPE25'
115C ELSE IF(INACTI==4) THEN
116C CHANGE LES COORDONNEES DES NOEUDS MAIN
117C WRITE(IOUT,'(A)')
118C . 'INACTI=4 IS NOT AVAILABLE FOR INTERFACE TYPE25'
119 ELSE IF(inacti==5) THEN
120C REDUCTION DU GAP
121 ELSE IF(inacti==-1) THEN
122C Initial penetrations <=> Initial forces
123 pene_old(5,j)= zero
124 ENDIF
125 ELSE
126C Reset (Same tracking will be done again in Engine)
127 irtlm(1,j)=0
128 irtlm(2,j)=0
129 irtlm(3,j)=0
130 END IF
131 END IF
132 100 CONTINUE
133C
134 RETURN
135 END
136!||====================================================================
137!|| i25cand ../starter/source/interfaces/inter3d1/i25pwr3.F
138!||--- called by ------------------------------------------------------
139!|| inint3 ../starter/source/interfaces/inter3d1/inint3.F
140!||====================================================================
141 SUBROUTINE i25cand(CAND_E,CAND_N,NSN ,IRTLM ,II_STOK ,
142 * NRTM ,MSEGTYP)
143C
144C-----------------------------------------------
145C I m p l i c i t T y p e s
146C-----------------------------------------------
147#include "implicit_f.inc"
148C-----------------------------------------------
149C C o m m o n B l o c k s
150C-----------------------------------------------
151 INTEGER CAND_E(*),CAND_N(*),NSN,IRTLM(4,*),II_STOK,
152 * NRTM,MSEGTYP(*)
153C-----------------------------------------------
154C L o c a l V a r i a b l e s
155C-----------------------------------------------
156 INTEGER E, I,ISH
157 .
158C-----------------------------------------------
159C E x t e r n a l F u n c t i o n s
160C-----------------------------------------------
161 ii_stok = 0
162 DO i=1,nsn
163 e = irtlm(1,i)
164 IF (e > 0) THEN
165 ii_stok =ii_stok + 1
166 cand_n(ii_stok) = i
167 cand_e(ii_stok) = e
168
169 ish = msegtyp(e)
170C
171Cf i25pen3.F <=> (ABS(ISH) /= 0 .AND. ABS(ISH) <= NRTM) .OR. ISH > NRTM
172 IF (ish /= 0)THEN
173C
174C coating shells and their opposite segment ::
175 IF(ish > nrtm)ish=ish-nrtm
176C
177 ii_stok =ii_stok + 1
178 cand_n(ii_stok) = i
179 cand_e(ii_stok) = abs(ish)
180 ENDIF
181
182 END IF
183 END DO
184C
185 RETURN
186 END
#define my_real
Definition cppsort.cpp:32
subroutine i25pwr3(itab, inacti, cand_e, cand_n, stfn, x, i_stok, nsv, iwpene, pene_old, noint, nty, msr, irtlm, irect, nsn, id, titr, mseglo, icont_i)
Definition i25pwr3.F:36
subroutine i25cand(cand_e, cand_n, nsn, irtlm, ii_stok, nrtm, msegtyp)
Definition i25pwr3.F:143
integer, parameter nchartitle
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