OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
recudis.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!|| recudis ../engine/source/implicit/recudis.F
25!||--- called by ------------------------------------------------------
26!|| imp_buck ../engine/source/implicit/imp_buck.F
27!|| lin_solv ../engine/source/implicit/lin_solv.F
28!||====================================================================
29 SUBROUTINE recudis(NDDL ,IDDL ,NDOF ,IKC ,LX ,
30 1 D ,DR ,INLOC )
31C-----------------------------------------------
32C I m p l i c i t T y p e s
33C-----------------------------------------------
34#include "implicit_f.inc"
35C-----------------------------------------------
36C C o m m o n B l o c k s
37C-----------------------------------------------
38#include "com04_c.inc"
39C-----------------------------------------------
40C D u m m y A r g u m e n t s
41C-----------------------------------------------
42 INTEGER NDDL,NDOF(*),IDDL(*),IKC(*),INLOC(*)
44 . d(3,*),dr(3,*),lx(*)
45C----------------------------------------------
46C L o c a l V a r i a b l e s
47C-----------------------------------------------
48 INTEGER I,J,K,NKC,ID,ND,M,N
49C----No ddl actuelle -> IDDL(NUMNOD)+J(1-6)-NKC-----
50 nkc=0
51 DO n = 1,numnod
52 i=inloc(n)
53 DO j=1,ndof(i)
54 nd = iddl(i)+j
55 id = nd-nkc
56 IF (j<=3) THEN
57 IF (ikc(nd)<1) THEN
58 d(j,i)=lx(id)
59 ELSE
60 nkc=nkc+1
61 ENDIF
62 ELSE
63 k=j-3
64 IF (ikc(nd)<1) THEN
65 dr(k,i)=lx(id)
66 ELSE
67 nkc=nkc+1
68 ENDIF
69 ENDIF
70 ENDDO
71 ENDDO
72C
73 RETURN
74 END
75!||====================================================================
76!|| recukin ../engine/source/implicit/recudis.F
77!||--- called by ------------------------------------------------------
78!|| imp_buck ../engine/source/implicit/imp_buck.F
79!|| imp_solv ../engine/source/implicit/imp_solv.F
80!|| rer02 ../engine/source/implicit/upd_glob_k.F
81!||--- calls -----------------------------------------------------
82!|| bc_imp2 ../engine/source/constraints/general/bcs/bc_imp0.F
83!|| fv_impd ../engine/source/constraints/general/impvel/fv_imp0.F
84!|| fvbc_impd ../engine/source/constraints/general/impvel/fv_imp0.F
85!|| i2_impd ../engine/source/interfaces/interf/i2_impd.F
86!|| rbe2_impd ../engine/source/constraints/general/rbe2/rbe2v.F
87!|| rbe3_impd ../engine/source/constraints/general/rbe3/rbe3v.F
88!|| rby_impd ../engine/source/constraints/general/rbody/rby_impd.F
89!|| rm_imp2 ../engine/source/model/remesh/rm_imp0.F
90!|| rwl_impd ../engine/source/constraints/general/rwall/srw_imp.F
91!||--- uses -----------------------------------------------------
92!|| imp_fvbcl ../engine/share/modules/impbufdef_mod.F
93!|| intbufdef_mod ../common_source/modules/interfaces/intbufdef_mod.F90
94!||====================================================================
95 SUBROUTINE recukin(RBY ,LPBY ,NPBY ,SKEW ,ISKEW ,
96 1 ITAB ,WEIGHT,MS ,IN ,
97 2 IBFV ,VEL ,ICODT,ICODR ,
98 3 NRBYAC,IRBYAC,NINT2 ,IINT2 ,IPARI ,
99 4 INTBUF_TAB ,NDOF ,D ,DR ,
100 5 X ,XFRAME,LJ ,IXR ,IXC ,
101 6 IXTG ,SH4TREE,SH3TREE,IRBE3 ,LRBE3,
102 7 FRBE3 ,IRBE2 ,LRBE2 )
103C-----------------------------------------------
104C M o d u l e s
105C-----------------------------------------------
106 USE imp_fvbcl
107 USE intbufdef_mod
108C-----------------------------------------------
109C I m p l i c i t T y p e s
110C-----------------------------------------------
111#include "implicit_f.inc"
112C-----------------------------------------------
113C C o m m o n B l o c k s
114C-----------------------------------------------
115#include "com04_c.inc"
116#include "param_c.inc"
117#include "remesh_c.inc"
118C-----------------------------------------------
119C D u m m y A r g u m e n t s
120C-----------------------------------------------
121 INTEGER IBFV(NIFV,*),LJ(*)
122 INTEGER WEIGHT(*),LPBY(*),NPBY(NNPBY,*),ITAB(*),
123 . IPARI(NPARI,*), ISKEW(*),
124 . NRBYAC,IRBYAC(*),NINT2 ,IINT2(*),IXR(*)
125 INTEGER NDOF(*),ICODT(*) ,ICODR(*),IXC(*),IXTG(*),
126 . SH4TREE(*), SH3TREE(*),IRBE3(NRBE3L,*),LRBE3(*),
127 . IRBE2(*),LRBE2(*)
128 my_real
129 . rby(nrby,*) ,skew(*),in(*),ms(*),
130 . vel(lfxvelr,*), xframe(nxframe,*),frbe3(*)
131 my_real
132 . x(3,*),d(3,*),dr(3,*)
133
134 TYPE(intbuf_struct_) INTBUF_TAB(*)
135C----------------------------------------------
136C L o c a l V a r i a b l e s
137C-----------------------------------------------
138 INTEGER I,J,K
139C-------pendant iteration dU_d=0------------
140C-------local FV-BCS coupling might modify global dirs due to unconsisting
141 IF(nfvbcl > 0 ) THEN
142 CALL fvbc_impd(ibfv ,skew ,xframe ,lj ,ndof ,
143 1 d ,dr ,icodt ,icodr ,iskew ,
144 2 ict_1 ,icr_1)
145 END IF
146 IF(nfxvel>0)THEN
147 CALL fv_impd(ibfv ,lj ,skew ,xframe ,d ,
148 1 dr )
149 ENDIF
150 CALL rwl_impd(d)
151 IF(nfvbcl > 0 ) THEN
152 CALL bc_imp2(ict_1 ,icr_1,iskew ,skew ,ndof ,
153 1 d ,dr )
154 ELSE
155 CALL bc_imp2(icodt ,icodr ,iskew ,skew ,ndof ,
156 1 d ,dr )
157 END IF
158 IF(nadmesh/=0)THEN
159 CALL rm_imp2(ixc ,ixtg ,d ,dr ,sh4tree,sh3tree)
160 ENDIF
161 IF(nrbyac>0)THEN
162 CALL rby_impd(nrbyac,irbyac,x ,rby,lpby,npby,skew,
163 1 iskew,itab,weight,ms ,in ,
164 2 ndof ,d ,dr ,ixr )
165 ENDIF
166 IF(nrbe3>0)THEN
167 CALL rbe3_impd(irbe3 ,lrbe3 ,x ,d ,dr ,
168 1 frbe3 ,skew )
169 ENDIF
170 IF(nrbe2>0)THEN
171 CALL rbe2_impd(irbe2 ,lrbe2 ,x ,d ,dr ,
172 1 skew )
173 ENDIF
174 CALL i2_impd(nint2 ,iint2,ipari,intbuf_tab ,
175 1 x ,ms ,in ,weight,ndof ,
176 2 d ,dr )
177C
178 RETURN
179 END
180!||====================================================================
181!|| iddl2nod ../engine/source/implicit/recudis.F
182!||--- called by ------------------------------------------------------
183!|| imp_solv ../engine/source/implicit/imp_solv.F
184!||====================================================================
185 SUBROUTINE iddl2nod(NDDL ,IDDL ,NDOF ,IKC ,INLOC ,
186 1 IID ,NN )
187C-----------------------------------------------
188C I m p l i c i t T y p e s
189C-----------------------------------------------
190#include "implicit_f.inc"
191C-----------------------------------------------
192C C o m m o n B l o c k s
193C-----------------------------------------------
194#include "com04_c.inc"
195C-----------------------------------------------
196C D u m m y A r g u m e n t s
197C-----------------------------------------------
198 INTEGER NDDL,NDOF(*),IDDL(*),IKC(*),INLOC(*),IID ,NN
199C----------------------------------------------
200C L o c a l V a r i a b l e s
201C-----------------------------------------------
202 INTEGER I,J,K,NKC,ID,ND,N
203C----No ddl actuelle -> IDDL(NUMNOD)+J(1-6)-NKC-----
204 NN=0
205 nkc=0
206 DO n = 1,numnod
207 i=inloc(n)
208 DO j=1,ndof(i)
209 nd = iddl(i)+j
210 id = nd-nkc
211 IF (ikc(nd)<1) THEN
212 IF (id==iid) THEN
213 nn=i
214 RETURN
215 ENDIF
216 ELSE
217 nkc=nkc+1
218 ENDIF
219 ENDDO
220 ENDDO
221C
222 RETURN
223 END
224!||====================================================================
225!|| weightddl ../engine/source/implicit/recudis.F
226!||--- called by ------------------------------------------------------
227!|| imp_chkm ../engine/source/implicit/imp_solv.F
228!|| imp_solv ../engine/source/implicit/imp_solv.F
229!||====================================================================
230 SUBROUTINE weightddl(IDDL ,NDOF ,IKC ,WEIGHT,W_IMP ,
231 1 INLOC )
232C-----------------------------------------------
233C I m p l i c i t T y p e s
234C-----------------------------------------------
235#include "implicit_f.inc"
236C-----------------------------------------------
237C C o m m o n B l o c k s
238C-----------------------------------------------
239#include "com04_c.inc"
240C-----------------------------------------------
241C D u m m y A r g u m e n t s
242C-----------------------------------------------
243 INTEGER NDOF(*),IDDL(*),IKC(*),INLOC(*),WEIGHT(*),W_IMP(*)
244C----------------------------------------------
245C L o c a l V a r i a b l e s
246C-----------------------------------------------
247 INTEGER I,J,K,NKC,ID,ND,M,N
248C----No ddl actuelle -> IDDL(NUMNOD)+J(1-6)-NKC-----
249 NKC=0
250 do n = 1,numnod
251 i=inloc(n)
252 DO j=1,ndof(i)
253 nd = iddl(i)+j
254 id = nd-nkc
255 IF (ikc(nd)<1) THEN
256 w_imp(id)=weight(i)
257 ELSE
258 nkc=nkc+1
259 ENDIF
260 ENDDO
261 ENDDO
262C
263 RETURN
264 END
subroutine bc_imp2(icodt, icodr, iskew, skew, ndof, d, dr)
Definition bc_imp0.F:618
#define my_real
Definition cppsort.cpp:32
subroutine fv_impd(ibfv, lj, skew, xframe, ud, rd)
Definition fv_imp0.F:932
subroutine fvbc_impd(ibfv, skew, xframe, lj, ndof, ud, rd, icodt, icodr, iskew, icodt1, icodr1)
Definition fv_imp0.F:3591
subroutine i2_impd(nint2, iint2, ipari, intbuf_tab, x, ms, in, weight, ndof, d, dr)
Definition i2_impd.F:35
subroutine rbe2_impd(irbe2, lrbe2, x, d, dr, skew)
Definition kinchk.F:1928
subroutine rbe3_impd(irbe3, lrbe3, x, d, dr, frbe3, skew)
Definition kinchk.F:1406
integer nfvbcl
integer, dimension(:), allocatable icr_1
integer, dimension(:), allocatable ict_1
subroutine rby_impd(nrbyac, irbyac, x, rby, lpby, npby, skew, iskew, itab, weight, ms, in, ndof, d, dr, ixr)
Definition rby_impd.F:37
subroutine recudis(nddl, iddl, ndof, ikc, lx, d, dr, inloc)
Definition recudis.F:31
subroutine iddl2nod(nddl, iddl, ndof, ikc, inloc, iid, nn)
Definition recudis.F:187
subroutine recukin(rby, lpby, npby, skew, iskew, itab, weight, ms, in, ibfv, vel, icodt, icodr, nrbyac, irbyac, nint2, iint2, ipari, intbuf_tab, ndof, d, dr, x, xframe, lj, ixr, ixc, ixtg, sh4tree, sh3tree, irbe3, lrbe3, frbe3, irbe2, lrbe2)
Definition recudis.F:103
subroutine weightddl(iddl, ndof, ikc, weight, w_imp, inloc)
Definition recudis.F:232
subroutine rm_imp2(ixc, ixtg, v, vr, sh4tree, sh3tree)
Definition rm_imp0.F:526
subroutine rwl_impd(ud)
Definition srw_imp.F:152