OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
srw_imp.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!|| fv_rwl ../engine/source/constraints/general/rwall/srw_imp.F
25!||--- called by ------------------------------------------------------
26!|| rgwal0_imp ../engine/source/constraints/general/rwall/rgwal0.F
27!||--- calls -----------------------------------------------------
28!|| l_dir0 ../engine/source/constraints/general/bcs/bc_imp0.F
29!||--- uses -----------------------------------------------------
30!|| imp_rwl ../engine/share/modules/impbufdef_mod.F
31!||====================================================================
32 SUBROUTINE fv_rwl(IDDL ,IKC ,NDOF ,UD ,V ,A )
33C-----------------------------------------------
34C M o d u l e s
35C-----------------------------------------------
36 USE imp_rwl
37C-----------------------------------------------
38C I m p l i c i t T y p e s
39C-----------------------------------------------
40#include "implicit_f.inc"
41C-----------------------------------------------
42C C o m m o n B l o c k s
43C-----------------------------------------------
44#include "com04_c.inc"
45#include "com08_c.inc"
46C-----------------------------------------------
47C D u m m y A r g u m e n t s
48C-----------------------------------------------
49 INTEGER IDDL(*),IKC(*),NDOF(*)
50C REAL
52 . ud(3,*), v(3,*), a(3,*)
53C-----------------------------------------------
54C L o c a l V a r i a b l e s
55C-----------------------------------------------
56 INTEGER N, I, J, K,I1,J1,K1,ND,ID,NL,IERR1,IERR2
57C REAL
58C-----------------------------------------------
59 n_rwl = 0
60 DO i = 1,numnod
61 IF (ndof(i)>0) THEN
62 nd = iddl(i)+1
63 IF (ikc(nd)==10) n_rwl=n_rwl+1
64 ENDIF
65 ENDDO
66 IF (n_rwl==0) RETURN
67C--------allocation------
68 IF(ALLOCATED(in_rwl)) DEALLOCATE(in_rwl)
69 ALLOCATE(in_rwl(n_rwl),stat=ierr1)
70 IF(ALLOCATED(nor_rwl)) DEALLOCATE(nor_rwl)
71 ALLOCATE(nor_rwl(3,n_rwl),stat=ierr2)
72 nl = 0
73 DO i = 1,numnod
74 IF (ndof(i)>0) THEN
75 nd = iddl(i)
76 IF (ikc(nd+1)==10) THEN
77 nl=nl+1
78 in_rwl(nl)=i
79 nor_rwl(1,nl) = a(1,i)
80 nor_rwl(2,nl) = a(2,i)
81 nor_rwl(3,nl) = a(3,i)
82 CALL l_dir0(nor_rwl(1,nl),j)
83 ud(j,i) = v(1,i)*dt2/nor_rwl(j,nl)
84 ikc(nd+1)=0
85 ikc(nd+j)=10
86 ENDIF
87 ENDIF
88 ENDDO
89C
90 RETURN
91 END
92!||====================================================================
93!|| fv_rwl0 ../engine/source/constraints/general/rwall/srw_imp.F
94!||--- called by ------------------------------------------------------
95!|| fv_rw0 ../engine/source/constraints/general/impvel/fv_imp0.F
96!||--- calls -----------------------------------------------------
97!|| fv_updk ../engine/source/constraints/general/impvel/fv_imp0.F
98!|| l_dir ../engine/source/constraints/general/bcs/bc_imp0.F
99!||--- uses -----------------------------------------------------
100!|| imp_rwl ../engine/share/modules/impbufdef_mod.F
101!||====================================================================
102 SUBROUTINE fv_rwl0(IDDL ,IFIX ,NDOF ,IADK ,JDIK ,
103 1 DIAG_K ,LT_K ,UD ,B )
104C-----------------------------------------------
105C M o d u l e s
106C-----------------------------------------------
107 USE imp_rwl
108C-----------------------------------------------
109C I m p l i c i t T y p e s
110C-----------------------------------------------
111#include "implicit_f.inc"
112C-----------------------------------------------
113C D u m m y A r g u m e n t s
114C-----------------------------------------------
115 INTEGER
116 . iddl(*),ifix(*),iadk(*),jdik(*),ndof(*)
117C REAL
118 my_real
119 . ud(3,*), diag_k(*),lt_k(*),b(*)
120C-----------------------------------------------
121C L o c a l V a r i a b l e s
122C-----------------------------------------------
123 INTEGER N, I, J, K,IR
124C REAL
125 my_real
126 . ej(3)
127C----------------sliding RW ->FXVEL local---------------
128 ir =0
129 DO i = 1,n_rwl
130 n=in_rwl(i)
131 ej(1)=nor_rwl(1,i)
132 ej(2)=nor_rwl(2,i)
133 ej(3)=nor_rwl(3,i)
134 CALL l_dir(ej,j)
135 CALL fv_updk(n ,iddl ,ej ,j ,ir ,
136 1 iadk ,jdik ,diag_k,lt_k ,b ,ud )
137 ENDDO
138C
139 RETURN
140 END
141!||====================================================================
142!|| rwl_impd ../engine/source/constraints/general/rwall/srw_imp.F
143!||--- called by ------------------------------------------------------
144!|| recukin ../engine/source/implicit/recudis.F
145!||--- calls -----------------------------------------------------
146!|| bc_updd ../engine/source/constraints/general/bcs/bc_imp0.F
147!|| l_dir ../engine/source/constraints/general/bcs/bc_imp0.F
148!||--- uses -----------------------------------------------------
149!|| imp_rwl ../engine/share/modules/impbufdef_mod.F
150!||====================================================================
151 SUBROUTINE rwl_impd(UD)
152C-----------------------------------------------
153C M o d u l e s
154C-----------------------------------------------
155 USE imp_rwl
156C-----------------------------------------------
157C I m p l i c i t T y p e s
158C-----------------------------------------------
159#include "implicit_f.inc"
160C-----------------------------------------------
161C D u m m y A r g u m e n t s
162C-----------------------------------------------
163 my_real
164 . ud(3,*)
165C-----------------------------------------------
166C L o c a l V a r i a b l e s
167C-----------------------------------------------
168 INTEGER N, I, J
169C REAL
170 my_real
171 . ej(3)
172C---------------------------------------------------------------
173 DO i = 1,n_rwl
174 n=in_rwl(i)
175 ej(1)=nor_rwl(1,i)
176 ej(2)=nor_rwl(2,i)
177 ej(3)=nor_rwl(3,i)
178 CALL l_dir(ej,j)
179 CALL bc_updd(n ,ej ,j ,ud )
180 ENDDO
181C
182 RETURN
183 END
184!||====================================================================
185!|| fv_rwlr0 ../engine/source/constraints/general/rwall/srw_imp.F
186!||--- called by ------------------------------------------------------
187!|| ext_rhs ../engine/source/implicit/upd_glob_k.F
188!|| upd_rhs ../engine/source/implicit/upd_glob_k.F
189!||--- calls -----------------------------------------------------
190!|| bc_updb ../engine/source/constraints/general/bcs/bc_imp0.F
191!|| l_dir ../engine/source/constraints/general/bcs/bc_imp0.F
192!||--- uses -----------------------------------------------------
193!|| imp_rwl ../engine/share/modules/impbufdef_mod.F
194!||====================================================================
195 SUBROUTINE fv_rwlr0(IDDL ,B )
196C-----------------------------------------------
197C M o d u l e s
198C-----------------------------------------------
199 USE imp_rwl
200C-----------------------------------------------
201C I m p l i c i t T y p e s
202C-----------------------------------------------
203#include "implicit_f.inc"
204C-----------------------------------------------
205C D u m m y A r g u m e n t s
206C-----------------------------------------------
207 INTEGER
208 . iddl(*)
209C REAL
210 my_real
211 . b(*)
212C-----------------------------------------------
213C L o c a l V a r i a b l e s
214C-----------------------------------------------
215 INTEGER N, I, J, K,IR,ID
216C REAL
217 my_real
218 . ej(3)
219C----------------sliding RW ->FXVEL local- RHS seulement--------------
220 ir =0
221 DO i = 1,n_rwl
222 n=in_rwl(i)
223 ej(1)=nor_rwl(1,i)
224 ej(2)=nor_rwl(2,i)
225 ej(3)=nor_rwl(3,i)
226 CALL l_dir(ej,j)
227 id = iddl(n)
228 CALL bc_updb(id ,ej ,j ,ir ,b )
229 ENDDO
230C
231 RETURN
232 END
subroutine l_dir(ej, j)
Definition bc_imp0.F:405
subroutine bc_updd(n, ej, j, d)
Definition bc_imp0.F:843
subroutine l_dir0(ej, j)
Definition bc_imp0.F:346
subroutine bc_updb(id, ej, jj, ir, lb)
Definition bc_imp0.F:1069
#define my_real
Definition cppsort.cpp:32
subroutine fv_updk(n, iddl, ej, jj, ir, iadk, jdik, diag_k, lt_k, lb, ud)
Definition fv_imp0.F:874
integer, dimension(:), allocatable in_rwl
integer n_rwl
subroutine fv_rwl0(iddl, ifix, ndof, iadk, jdik, diag_k, lt_k, ud, b)
Definition srw_imp.F:104
subroutine rwl_impd(ud)
Definition srw_imp.F:152
subroutine fv_rwlr0(iddl, b)
Definition srw_imp.F:196
subroutine fv_rwl(iddl, ikc, ndof, ud, v, a)
Definition srw_imp.F:33