OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
gendynain.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!|| gendynain ../engine/source/output/dynain/gendynain.F
25!||--- called by ------------------------------------------------------
26!|| sortie_main ../engine/source/output/sortie_main.f
27!||--- calls -----------------------------------------------------
28!|| ancmsg ../engine/source/output/message/message.F
29!|| arret ../engine/source/system/arret.F
30!|| close_c ../common_source/tools/input_output/write_routtines.c
31!|| cur_fil_c ../common_source/tools/input_output/write_routtines.c
32!|| dynain_c_strag ../engine/source/output/dynain/dynain_c_strag.F
33!|| dynain_c_strsg ../engine/source/output/dynain/dynain_c_strsg.F
34!|| dynain_node ../engine/source/output/dynain/dynain_node.F
35!|| dynain_shel_mp ../engine/source/output/dynain/dynain_shel_mp.F
36!|| dynain_shel_spmd ../engine/source/output/dynain/dynain_shel_spmd.F
37!|| dynain_size_c ../engine/source/output/dynain/dynain_size.F
38!|| open_c ../common_source/tools/input_output/write_routtines.c
39!|| spmd_outpitab ../engine/source/mpi/interfaces/spmd_outp.F
40!|| strs_txt50 ../engine/source/output/sta/sta_txt.F
41!||--- uses -----------------------------------------------------
42!|| drape_mod ../engine/share/modules/drape_mod.F
43!|| elbufdef_mod ../common_source/modules/mat_elem/elbufdef_mod.F90
44!|| inoutfile_mod ../common_source/modules/inoutfile_mod.F
45!|| matparam_def_mod ../common_source/modules/mat_elem/matparam_def_mod.f90
46!|| message_mod ../engine/share/message_module/message_mod.F
47!|| stack_mod ../engine/share/modules/stack_mod.F
48!|| state_mod ../common_source/modules/state_mod.F
49!||====================================================================
50 SUBROUTINE gendynain(X ,ELBUF_TAB, BUFEL ,IXC ,IXTG ,
51 2 IPARG ,IPM , IGEO ,ITAB ,IPART ,
52 3 PM ,GEO , IPARTC ,IPARTTG ,LENG ,
53 4 LENGC ,LENGTG , WEIGHT ,NODGLOB ,THKE ,
54 5 NPBY ,LPBY , STACK ,DRAPE_SH4N ,DRAPE_SH3N ,
55 6 DYNAIN_DATA,DRAPEG ,MAT_PARAM)
56C-----------------------------------------------
57C M o d u l e s
58C-----------------------------------------------
59 USE elbufdef_mod
60 USE matparam_def_mod
61 USE message_mod
62 USE inoutfile_mod
63 USE stack_mod
64 USE drape_mod
65 USE state_mod
66C-----------------------------------------------
67C I m p l i c i t T y p e s
68C-----------------------------------------------
69#include "implicit_f.inc"
70C-----------------------------------------------
71C C o m m o n B l o c k s
72C-----------------------------------------------
73#include "com01_c.inc"
74#include "com04_c.inc"
75#include "param_c.inc"
76#include "units_c.inc"
77#include "scr17_c.inc"
78#include "chara_c.inc"
79#include "task_c.inc"
80C-----------------------------------------------
81C D u m m y A r g u m e n t s
82C-----------------------------------------------
83 INTEGER IPARG(*),
84 . IXC(NIXC,*),IXTG(NIXTG,*),IPM(*),IGEO(*),
85 . ITAB(*) ,IPART(LIPART1,*) ,IPARTC(*) ,IPARTTG(*),
86 . WEIGHT(*), NODGLOB(*), NPBY(NNPBY,*), LPBY(*)
87 INTEGER LENG,LENGC,LENGTG
89 . x(*), bufel(*),
90 . pm(npropm,*), geo(npropg,*) ,thke(*)
91 TYPE (ELBUF_STRUCT_), DIMENSION(NGROUP), TARGET :: ELBUF_TAB
92 TYPE (STACK_PLY) :: STACK
93 TYPE (DRAPE_) :: DRAPE_SH4N(NUMELC_DRAPE),DRAPE_SH3N(NUMELTG_DRAPE)
94 TYPE (DRAPEG_) :: DRAPEG
95 TYPE (DYNAIN_DATABASE), INTENT(INOUT) :: DYNAIN_DATA
96 TYPE (MATPARAM_STRUCT_) ,DIMENSION(NUMMAT) ,INTENT(IN) :: MAT_PARAM
97C-----------------------------------------------
98C L o c a l V a r i a b l e s
99C-----------------------------------------------
100 CHARACTER CHSTAT*4,FILNAM*100,T10*10,MES*40
101 INTEGER FILEN,I,INNODA,IERR,J,N
102 INTEGER LENR,SIZLOC,SIZP0
103 INTEGER , DIMENSION(:),ALLOCATABLE :: ITABG, NODTAG ,DYNAIN_INDXC ,
104 . DYNAIN_INDXTG
105 INTEGER CTEXT(2149)
106 double precision
107 . , DIMENSION(:),ALLOCATABLE :: wa,wap0
108
109 INTEGER :: LEN_TMP_NAME
110 CHARACTER(len=2148) :: TMP_NAME
111 LOGICAL IS_FILE_TO_BE_WRITTEN
112 CHARACTER*100 LINE
113C-----------------------------------------------
114C S o u r c e L i n e s
115C-----------------------------------------------
116C===============================================|
117C OPEN FILE
118C-----------------------------------------------
119 IF(dynain_data%IDYNAINF>=10000)dynain_data%IDYNAINF=1
120 WRITE(chstat,'(I4.4)')dynain_data%IDYNAINF
121 IF(dynain_data%ZIPDYNAIN==0) THEN ! Not zipped file
122 filnam=rootnam(1:rootlen)//'_'//chstat//'.dynain'
123 filen = rootlen + 12
124 len_tmp_name = outfile_name_len + filen
125 tmp_name=outfile_name(1:outfile_name_len)//filnam(1:filen)
126 IF(ispmd == 0) THEN
127 OPEN(unit=iudynain,file=tmp_name(1:len_tmp_name),access='SEQUENTIAL',form='FORMATTED',status='UNKNOWN')
128 WRITE(iudynain,'(2A)')'$RADIOSS DYNAIN FILE ',filnam(1:filen)
129 END IF
130 ELSE ! zipped file
131 filnam=rootnam(1:rootlen)//'_'//chstat//'.dynain'
132 filen = rootlen + 12
133 len_tmp_name = outfile_name_len + filen
134 tmp_name=outfile_name(1:outfile_name_len)//filnam(1:filen)
135 DO i=1,len_tmp_name
136 ctext(i)=ichar(tmp_name(i:i))
137 CALL cur_fil_c(0)
138 ENDDO
139 IF(ispmd == 0) THEN
140 CALL open_c(ctext,len_tmp_name,6)
141 WRITE(line,'(2A)') '$RADIOSS DYNAIN FILE ',filnam(1:filen)
142 CALL strs_txt50(line,100)
143 ENDIF
144 ENDIF
145
146c
147
148C-----------------------
149C Allocation Tabs
150C-----------------------
151 ALLOCATE(nodtag(numnod),stat=ierr)
152 ALLOCATE(itabg(leng),stat=ierr)
153 ALLOCATE(dynain_indxc(2*lengc),stat=ierr)
154 ALLOCATE(dynain_indxtg(2*lengtg),stat=ierr)
155C-----------------------------------------------
156C CONNECTIVITIES + NODAL COORDINATES
157C-----------------------------------------------
158c
159 IF (nspmd > 1)CALL spmd_outpitab(itab,weight,nodglob,itabg)
160
161 nodtag=0
162
163 dynain_data%DYNAIN_NUMELC =0
164 dynain_data%DYNAIN_NUMELTG =0
165
166 IF(nspmd == 1)THEN
167 ! - shells -
168 CALL dynain_shel_mp(itab ,itabg ,leng ,igeo ,ixc ,
169 . ixtg ,ipartc ,iparttg ,dynain_data ,
170 . nodtag ,dynain_indxc,dynain_indxtg,iparg ,
171 . elbuf_tab,thke ,ipart )
172 dynain_data%DYNAIN_NUMELC_G =dynain_data%DYNAIN_NUMELC
173 dynain_data%DYNAIN_NUMELTG_G =dynain_data%DYNAIN_NUMELTG
174 ELSE
175 ! - shells -
176 CALL dynain_shel_spmd(itab ,itabg ,leng ,igeo ,ixc ,
177 . ixtg ,ipartc ,iparttg ,dynain_data ,
178 . nodtag ,dynain_indxc,dynain_indxtg,iparg ,
179 . elbuf_tab,thke ,lengc ,lengtg ,ipart )
180 END IF
181
182
183C-----------------------------------------------
184C RIGID BODY'S PRIMARY NODE IS OUTPUTTED IF ONE OF ITS SECONDARY NODES ARE
185C-----------------------------------------------
186 DO i=1,nrbody
187 DO j=1,npby(2,i)
188 n=lpby(npby(11,i)+j)
189 IF (nodtag(n)/=0) THEN
190 nodtag(npby(1,i)) = 1
191 EXIT
192 END IF
193 ENDDO
194 ENDDO
195C-----------------------------------------------
196 CALL dynain_node(x,numnod,itab,itabg,leng,nodglob,weight,nodtag,dynain_data)
197
198C-----------------------------------------------
199 CALL dynain_size_c(iparg ,elbuf_tab, sizp0 ,sizloc ,dynain_data )
200
201C-----------------------------------------------
202C ALLOCATION OF TABLES
203C-----------------------------------------------
204 ierr = 0
205 IF(sizloc >= 1) THEN
206 ALLOCATE(wa(sizloc),stat=ierr)
207 ELSE
208 ALLOCATE(wa(1))
209 ENDIF
210 IF(ierr/=0)THEN
211 CALL ancmsg(msgid=252,anmode=aninfo,
212 . i1=ierr)
213 CALL arret(2)
214 END IF
215
216 ierr = 0
217 sizp0 = max(1,sizp0)
218 ALLOCATE(wap0(sizp0),stat=ierr)
219 IF(ierr/=0)THEN
220 CALL ancmsg(msgid=252,anmode=aninfo,
221 . i1=ierr)
222 CALL arret(2)
223 END IF
224C-----------------------------------------------
225C SHELL SCALAR
226C-----------------------------------------------
227
228
229 IF(dynain_data%DYNAIN_C(4)==1) THEN
230 CALL dynain_c_strsg(
231 1 elbuf_tab ,iparg ,igeo ,ixc ,
232 2 ixtg ,wa ,wap0 ,ipartc,iparttg,
233 3 dynain_data,dynain_indxc,dynain_indxtg,sizp0 ,
234 4 geo ,stack ,drape_sh4n ,drape_sh3n,x ,
235 5 thke , drapeg ,nummat ,mat_param )
236 ENDIF
237C------------------------------------------
238
239 IF(dynain_data%DYNAIN_C(5)==1) THEN
240 CALL dynain_c_strag(
241 1 elbuf_tab ,iparg ,ipm ,igeo ,ixc ,
242 2 ixtg ,wa ,wap0 ,ipartc,iparttg,
243 3 dynain_data,dynain_indxc,dynain_indxtg,sizp0 ,
244 4 geo ,stack ,drape_sh4n ,drape_sh3n,x ,
245 5 thke ,drapeg)
246 ENDIF
247
248C-----------------------------------------------
249
250 IF(sizloc >= 1) DEALLOCATE(wa)
251 IF(sizp0 >= 1) DEALLOCATE(wap0)
252C-----------------------
253C DEAllocation Tabs
254C-----------------------
255 DEALLOCATE(nodtag,itabg,dynain_indxc,dynain_indxtg)
256C-----------------------------------------------
257C END
258C-----------------------------------------------
259 IF(ispmd==0) THEN
260 IF(dynain_data%ZIPDYNAIN==0) THEN
261 WRITE(iudynain,'(A)')'*END '
262 CLOSE(unit=iudynain)
263 ELSE
264 CALL strs_txt50('*END ',7)
265 CALL close_c()
266 ENDIF
267
268 WRITE (iout,1000) filnam(1:filen)
269 WRITE (istdo,1000) filnam(1:filen)
270 ENDIF
271
272
273 1000 FORMAT (4x,' DYNAIN FILE:',1x,a,' WRITTEN')
274C
275 RETURN
276 END
#define my_real
Definition cppsort.cpp:32
subroutine dynain_c_strag(elbuf_tab, iparg, ipm, igeo, ixc, ixtg, wa, wap0, ipartc, iparttg, dynain_data, dynain_indxc, dynain_indxtg, sizp0, geo, stack, drape_sh4n, drape_sh3n, x, thke, drapeg)
subroutine dynain_c_strsg(elbuf_tab, iparg, igeo, ixc, ixtg, wa, wap0, ipartc, iparttg, dynain_data, dynain_indxc, dynain_indxtg, sizp0, geo, stack, drape_sh4n, drape_sh3n, x, thke, drapeg, nummat, mat_param)
subroutine dynain_node(x, numnod, itab, itabg, leng, nodglob, weight, nodtag, dynain_data)
Definition dynain_node.F:35
subroutine dynain_shel_mp(itab, itabg, leng, igeo, ixc, ixtg, ipartc, iparttg, dynain_data, nodtag, dynain_indxc, dynain_indxtg, iparg, elbuf_tab, thke, ipart)
subroutine dynain_shel_spmd(itab, itabg, leng, igeo, ixc, ixtg, ipartc, iparttg, dynain_data, nodtag, dynain_indxc, dynain_indxtg, iparg, elbuf_tab, thke, lengc, lengtg, ipart)
subroutine dynain_size_c(iparg, elbuf_tab, p0ars, wasz, dynain_data)
Definition dynain_size.F:34
subroutine gendynain(x, elbuf_tab, bufel, ixc, ixtg, iparg, ipm, igeo, itab, ipart, pm, geo, ipartc, iparttg, leng, lengc, lengtg, weight, nodglob, thke, npby, lpby, stack, drape_sh4n, drape_sh3n, dynain_data, drapeg, mat_param)
Definition gendynain.F:56
#define max(a, b)
Definition macros.h:21
character(len=outfile_char_len) outfile_name
integer outfile_name_len
subroutine sortie_main(timers, pm, d, v, ale_connect, w, elbuf, iparg, ixs, ixq, ixc, ixt, ixp, ixr, ixtg, wa, itab, x, geo, ms, a, cont, partsav, icut, xcut, fint, fext, fopt, anin, lpby, npby, nstrf, rwbuf, nprw, ebcs_tab, tani, inoise, bufnois, rby, neflsw, nnflsw, crflsw, flsw, lout, nodes, fsav, skew, elbuf_tab, cluster, vr, in, weight, fcluster, mcluster, dd_iad, dmas, accelm, gauge, ipari, eani, ipart, mat_param, igrnod, subset, nom_opt, ar, igrsurf, bufsf, idata, rdata, kxx, ixx, bufmat, bufgeo, kxsp, ixsp, nod2sp, spbuf, dr, fsavd, ixri, rivet, iskwn, iframe, xframe, ixs10, ixs20, ixs16, ndma, monvol, volmon, ipm, igeo, nodglob, iad_elem, fr_elem, fr_rby2, iad_rby2, fr_wall, fr_sec, fxbipm, fxbrpm, ndin, fxbdep, fxbvit, fxbacc, iflow, rflow, ipartl, npartl, iaccp, naccp, fasolfr, fncont, ftcont, iparth, fr_mv, ipart_state, sh4tree, sh3tree, temp, thke, err_thk_sh4, err_thk_sh3, inod_pxfem, fthreac, nodreac, gresav, diag_sms, sh4trim, sh3trim, fncont2, xmom_sms, irbe2, irbe3, lrbe2, lrbe3, fr_rbe2, fr_rbe3m, iad_rbe2, dxancg, iel_pxfem, zi_ply, vgaz, fcontg, fncontg, ftcontg, fanreac, inod_crk, iel_crk, elcutc, iadc_crk, pdama2, res_sms, sensors, qfricint, igaup, ngaup, weight_md, ncont, indexcont, nodglobxfe, nodedge, xfem_tab, nv46, rthbuf, kxig3d, ixig3d, knot, wige, nercvois, nesdvois, lercvois, lesdvois, crkedge, stack, isphio, vsphio, icode, indx_crk, xedge4n, xedge3n, sph2sol, stifn, stifr, drape_sh4n, drape_sh3n, ms_2d, multi_fvm, segquadfr, h3d_data, iskew, pskids, iskwp, knotlocpc, knotlocel, pinch_data, tag_skins6, irunn_bis, tf, npc, dynain_data, fcont_max, mds_matid, fncontp2, ftcontp2, ibcl, iloadp, lloadp, loadp, tagncont, loadp_hyd_inter, forc, drapeg, user_windows, output, dt, fsavsurf, table, loads, sfani, iparit, x_c, sz_npcont2, npcont2, glob_therm, pblast, wfext)
subroutine spmd_outpitab(v, weight, nodglob, vglob)
Definition spmd_outp.F:1077
subroutine strs_txt50(text, length)
Definition sta_txt.F:87
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
subroutine arret(nn)
Definition arret.F:87
void close_c()
void cur_fil_c(int *nf)
void open_c(int *ifil, int *len, int *mod)