OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
userwindow_interface_routines.F File Reference
#include "implicit_f.inc"
#include "com04_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine userwi_read (user_windows, ispmd, nspmd, numnod)
subroutine userwi_write (user_windows, ispmd, nspmd, numnod)
subroutine get_user_window_nodes (internal_id, user_id)
subroutine userwindow_get_a (a_buf)
subroutine userwindow_get_ar (ar_buf)

Function/Subroutine Documentation

◆ get_user_window_nodes()

subroutine get_user_window_nodes ( integer, dimension(user_windows%n_usernods), intent(inout) internal_id,
integer, dimension(user_windows%n_usernods), intent(inout) user_id )

Definition at line 205 of file userwindow_interface_routines.F.

206!$COMMENT
207 ! -----------------------------------------------
208 ! ROUTINE DESCRIPTION :
209 ! ===================
210 ! CALLBACK Routine Give to user Windows the list of nodes
211 ! As engine nodes & user nodes
212 ! ------------------------------------------------
213 ! DUMMY ARGUMENTS DESCRIPTION:
214 ! ===================
215 !
216 ! NAME DESCRIPTION
217 !
218 ! INTERNAL_ID : internal list
219 ! USER_ID : user id list
220 !------------------------------------------------------------------
221!$ENDCOMMENT
222C-----------------------------------------------
223C M o d u l e s
224C-----------------------------------------------
225 USE user_interface_mod
226 USE restmod
227C-----------------------------------------------
228C C o m m o n B l o c k s
229C-----------------------------------------------
230#include "implicit_f.inc"
231C-----------------------------------------------
232C D u m m y A r g u m e n t s
233C-----------------------------------------------
234 INTEGER,intent(INOUT),DIMENSION(USER_WINDOWS%N_USERNODS) :: INTERNAL_ID
235 INTEGER,intent(INOUT),DIMENSION(USER_WINDOWS%N_USERNODS) :: USER_ID
236C-----------------------------------------------
237C L o c a l V a r i a b l e s
238C-----------------------------------------------
239 INTEGER I,ND
240C-----------------------------------------------
241 IF(user_windows%HAS_USER_WINDOW /= 0)THEN
242 DO i=1,user_windows%N_USERNODS
243 nd = user_windows%USERNODS(i)
244 internal_id(i)=nd
245! USER_ID(I)=ITAB(ND)
246 user_id(i) = 0
247 ENDDO
248 ENDIF

◆ userwi_read()

subroutine userwi_read ( type(user_windows_), intent(inout) user_windows,
integer, intent(in) ispmd,
integer, intent(in) nspmd,
integer, intent(in) numnod )

Definition at line 34 of file userwindow_interface_routines.F.

35!$COMMENT
36! -----------------------------------------------
37! ROUTINE DESCRIPTION :
38! ===================
39! Read Userlib Restart
40! ------------------------------------------------
41! DUMMY ARGUMENTS DESCRIPTION:
42! ===================
43!
44! NAME DESCRIPTION
45!
46! USER_WINDOWS USER Windows type
47! ISPMD Current SPMD domains
48! NSPMD #SPMD domains
49!------------------------------------------------------------------
50!$ENDCOMMENT
51C-----------------------------------------------
52C M o d u l e s
53C-----------------------------------------------
54 USE message_mod
56C-----------------------------------------------
57C I m p l i c i t T y p e s
58C-----------------------------------------------
59#include "implicit_f.inc"
60C-----------------------------------------------
61C D u m m y A r g u m e n t s
62C-----------------------------------------------
63 TYPE(USER_WINDOWS_),INTENT(INOUT) :: USER_WINDOWS
64 INTEGER ,INTENT(IN) :: ISPMD
65 INTEGER ,INTENT(IN) :: NSPMD
66 INTEGER ,INTENT(IN) :: NUMNOD
67C-----------------------------------------------
68C L o c a l V a r i a b l e s
69C-----------------------------------------------
70C-----------------------------------------------
71C S o u r c e L i n e s
72C-----------------------------------------------
73 CALL read_i_c(user_windows%HAS_USER_WINDOW,1)
74
75 IF(user_windows%HAS_USER_WINDOW /= 0 ) THEN
76
77 IF (ispmd == 0)THEN
78 CALL read_i_c(user_windows%NUVAR,1)
79 CALL read_i_c(user_windows%NUVARI,1)
80 CALL read_i_c(user_windows%S_IUSER,1)
81 CALL read_i_c(user_windows%S_USER,1)
82 CALL read_i_c(user_windows%N_USERNODS,1)
83
84 ALLOCATE(user_windows%IUSER(user_windows%S_IUSER))
85 ALLOCATE(user_windows%USER(user_windows%S_USER))
86 ALLOCATE(user_windows%USERNODS(user_windows%N_USERNODS))
87
88 CALL read_i_c(user_windows%IUSER,user_windows%S_IUSER)
89 CALL read_db(user_windows%USREINT,1)
90 CALL read_db(user_windows%USER,user_windows%S_USER)
91 CALL read_i_c(user_windows%USERNODS,user_windows%N_USERNODS)
92
93 ! SPMD Structures
94 CALL read_i_c(user_windows%S_FR_USERW,1)
95 ALLOCATE(user_windows%IAD_USERW(nspmd+1))
96 ALLOCATE(user_windows%FR_USERW(user_windows%S_FR_USERW))
97
98 CALL read_i_c(user_windows%IAD_USERW,nspmd+1)
99 CALL read_i_c(user_windows%FR_USERW,user_windows%S_FR_USERW)
100
101 ! SAV & AR_SAV on ispmd==0
102 ALLOCATE(user_windows%A_SAV(3,numnod))
103 ALLOCATE(user_windows%AR_SAV(3,numnod))
104 CALL read_db(user_windows%A_SAV,3*numnod)
105 CALL read_db(user_windows%AR_SAV,3*numnod)
106
107 ! ALLOCATE WA to 3x NUMNOD
108 user_windows%S_WA = 3*numnod
109 ALLOCATE(user_windows%WA(3*numnod))
110 ELSE
111 CALL read_i_c(user_windows%S_FR_USERW,1)
112
113 ALLOCATE(user_windows%FR_USERW(user_windows%S_FR_USERW))
114
115 CALL read_i_c(user_windows%FR_USERW,user_windows%S_FR_USERW)
116
117 ENDIF
118 ENDIF
subroutine read_db(a, n)
Definition read_db.F:88
void read_i_c(int *w, int *len)

◆ userwi_write()

subroutine userwi_write ( type(user_windows_), intent(in) user_windows,
integer, intent(in) ispmd,
integer, intent(in) nspmd,
integer, intent(in) numnod )

Definition at line 131 of file userwindow_interface_routines.F.

132!$COMMENT
133 ! -----------------------------------------------
134 ! ROUTINE DESCRIPTION :
135 ! ===================
136 ! WRITE Userlib Restart
137 ! ------------------------------------------------
138 ! DUMMY ARGUMENTS DESCRIPTION:
139 ! ===================
140 !
141 ! NAME DESCRIPTION
142 !
143 ! USER_WINDOWS USER Windows type
144 ! ISPMD Current SPMD domains
145 ! NSPMD #SPMD domains
146 !------------------------------------------------------------------
147!$ENDCOMMENT
148C-----------------------------------------------
149C M o d u l e s
150C-----------------------------------------------
151 USE message_mod
153C-----------------------------------------------
154C I m p l i c i t T y p e s
155C-----------------------------------------------
156#include "implicit_f.inc"
157C-----------------------------------------------
158C D u m m y A r g u m e n t s
159C-----------------------------------------------
160 TYPE(USER_WINDOWS_),INTENT(IN) :: USER_WINDOWS
161 INTEGER ,INTENT(IN) :: ISPMD
162 INTEGER ,INTENT(IN) :: NSPMD
163 INTEGER ,INTENT(IN) :: NUMNOD
164
165 CALL write_i_c(user_windows%HAS_USER_WINDOW,1)
166 IF(user_windows%HAS_USER_WINDOW /= 0 ) THEN
167
168 IF (ispmd == 0)THEN
169
170 CALL write_i_c(user_windows%NUVAR,1)
171 CALL write_i_c(user_windows%NUVARI,1)
172 CALL write_i_c(user_windows%S_IUSER,1)
173 CALL write_i_c(user_windows%S_USER,1)
174 CALL write_i_c(user_windows%N_USERNODS,1)
175
176 CALL write_i_c(user_windows%IUSER,user_windows%S_IUSER)
177 CALL write_db(user_windows%USREINT,1)
178 CALL write_db(user_windows%USER,user_windows%S_USER)
179 CALL write_i_c(user_windows%USERNODS,user_windows%N_USERNODS)
180
181 ! SPMD Structures
182 CALL write_i_c(user_windows%S_FR_USERW,1)
183 CALL write_i_c(user_windows%IAD_USERW,nspmd+1)
184 CALL write_i_c(user_windows%FR_USERW,user_windows%S_FR_USERW)
185
186 ! A_SAV & AR_SAV
187 CALL write_db(user_windows%A_SAV,3*numnod)
188 CALL write_db(user_windows%AR_SAV,3*numnod)
189
190 ELSE
191
192 CALL write_i_c(user_windows%S_FR_USERW,1)
193 CALL write_i_c(user_windows%FR_USERW,user_windows%S_FR_USERW)
194
195 ENDIF
196 ENDIF
197
subroutine write_db(a, n)
Definition write_db.F:140
void write_i_c(int *w, int *len)

◆ userwindow_get_a()

subroutine userwindow_get_a ( double precision, dimension(3,numnod) a_buf)

Definition at line 257 of file userwindow_interface_routines.F.

258C-----------------------------------------------
259C M o d u l e s
260C-----------------------------------------------
261 USE user_interface_mod
262C-----------------------------------------------
263C I m p l i c i t T y p e s
264C-----------------------------------------------
265#include "implicit_f.inc"
266C-----------------------------------------------
267C C o m m o n B l o c k s
268C-----------------------------------------------
269#include "com04_c.inc"
270C-----------------------------------------------
271C D u m m y A r g u m e n t s
272C-----------------------------------------------
273 DOUBLE PRECISION A_BUF(3,NUMNOD)
274C-----------------------------------------------
275C L o c a l V a r i a b l e s
276C-----------------------------------------------
277 INTEGER I,ND
278C-----------------------------------------------
279 IF(user_windows%HAS_USER_WINDOW /= 0)THEN
280 DO i=1,user_windows%N_USERNODS
281 nd = user_windows%USERNODS(i)
282 a_buf(1,i)=user_windows%A_SAV(1,nd)
283 a_buf(2,i)=user_windows%A_SAV(2,nd)
284 a_buf(3,i)=user_windows%A_SAV(3,nd)
285 ENDDO
286 ENDIF

◆ userwindow_get_ar()

subroutine userwindow_get_ar ( double precision, dimension(3,numnod) ar_buf)

Definition at line 293 of file userwindow_interface_routines.F.

294C-----------------------------------------------
295C M o d u l e s
296C-----------------------------------------------
297 USE user_interface_mod
298C-----------------------------------------------
299C I m p l i c i t T y p e s
300C-----------------------------------------------
301#include "implicit_f.inc"
302C-----------------------------------------------
303C C o m m o n B l o c k s
304C-----------------------------------------------
305#include "com04_c.inc"
306C-----------------------------------------------
307C D u m m y A r g u m e n t s
308C-----------------------------------------------
309 DOUBLE PRECISION AR_BUF(3,NUMNOD)
310C-----------------------------------------------
311C L o c a l V a r i a b l e s
312C-----------------------------------------------
313 INTEGER I,ND
314C-----------------------------------------------
315 IF(user_windows%HAS_USER_WINDOW /= 0)THEN
316 DO i=1,user_windows%N_USERNODS
317 nd = user_windows%USERNODS(i)
318 ar_buf(1,i)=user_windows%AR_SAV(1,nd)
319 ar_buf(2,i)=user_windows%AR_SAV(2,nd)
320 ar_buf(3,i)=user_windows%AR_SAV(3,nd)
321 ENDDO
322 ENDIF