OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
h3d_oned_vector.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!|| h3d_oned_vector ../engine/source/output/h3d/h3d_results/h3d_oned_vector.F
25!||--- called by ------------------------------------------------------
26!|| genh3d ../engine/source/output/h3d/h3d_results/genh3d.f
27!||--- calls -----------------------------------------------------
28!|| h3d_write_vector ../engine/source/output/h3d/h3d_results/h3d_write_vector.F
29!||--- uses -----------------------------------------------------
30!|| elbufdef_mod ../common_source/modules/mat_elem/elbufdef_mod.F90
31!|| names_and_titles_mod ../common_source/modules/names_and_titles_mod.F
32!||====================================================================
33 SUBROUTINE h3d_oned_vector(
34 . ELBUF_TAB , IFUNC , IPARG , GEO , IXT ,
35 . IXP , IXR , PM , ANIM ,
36 . ONED_VECTOR , ID_ELEM , ITY_ELEM , INFO1 , INFO2 ,
37 . IS_WRITTEN_ONED, IPARTT , IPARTP , IPARTR, H3D_PART,
38 . KEYWORD , X , D , TORS )
39C-----------------------------------------------
40C M o d u l e s
41C-----------------------------------------------
42 USE elbufdef_mod
44C-----------------------------------------------
45C I m p l i c i t T y p e s
46C-----------------------------------------------
47#include "implicit_f.inc"
48C-----------------------------------------------
49C C o m m o n B l o c k s
50C-----------------------------------------------
51#include "mvsiz_p.inc"
52#include "com01_c.inc"
53#include "com04_c.inc"
54#include "param_c.inc"
55C-----------------------------------------------
56C D u m m y A r g u m e n t s
57C-----------------------------------------------
58C REAL
60 . pm(npropm,*), geo(npropg,*),
61 . anim(*),oned_vector(3,*),x(3,*),d(3,*),tors(15,*)
62 INTEGER IPARG(NPARG,*),
63 . IXT(NIXT,*),IXP(NIXP,*),IXR(NIXR,*),IFUNC,
64 . nanim1d_l,
65 . is_written_oned(*),id_elem(*),ity_elem(*),
66 . ipartt(*) ,ipartp(*),ipartr(*),h3d_part(*)
67 INTEGER BUF,INFO1,INFO2
68C
69 TYPE (ELBUF_STRUCT_), DIMENSION(NGROUP), TARGET :: ELBUF_TAB
70 CHARACTER(LEN=NCHARLINE100) :: KEYWORD
71C-----------------------------------------------
72C L o c a l V a r i a b l e s
73C-----------------------------------------------
74C REAL
76 . evar(mvsiz), mass(mvsiz) ,
77 . off, p, vonm2, vonm, s1, s2, s12, s3, value(3),
78 . a1,b1,b2,b3,yeq,f1,m1,m2,m3, xm,
79 . for, area, feq, eplas, rho0, a0, xx1, yy1, zz1, al0
80 INTEGER I, II, NG, NEL, NFT, IAD, ITY, LFT, NPT, ISS, ISC,
81 . IADD, N, J, LLT, MLW, NB1, NB2, NB3, NB4, NB5,
82 . NB6, NB7, NB8, NB9, NB10, NB11, NB12, NB13, NB14, NB15,
83 . NB16, LLL,NUVAR,IGTYP,
84 . ISTRAIN,NN, K1, K2,JTURB,MT,JALE, IMID, IALEL,IPID,
85 . nn1,nn2,nn3,nn4,nn5,nn6,nn7,nn8,nn9,nn10,nf,
86 . offset,k,inc,kk,ihbe,isrot,ilayer,ir,is,jj(6),iok_part(mvsiz),
87 . is_written_value(mvsiz),n1, n2
88 REAL R4
89C
90 TYPE(G_BUFEL_) ,POINTER :: GBUF
91 TYPE(L_BUFEL_),POINTER :: LBUF
92C-----------------------------------------------
93C
94 nn1 = 1
95 nn3 = 1
96 nn4 = nn3
97 nn5 = nn4
98 nn6 = nn5
99 nn7 = nn6 + numelt
100 nn8 = nn7 + numelp
101 nn9 = nn8 + numelr
102 nn10= nn9
103C
104 DO ng=1,ngroup
105 mlw =iparg(1,ng)
106 nel =iparg(2,ng)
107 ity =iparg(5,ng)
108 igtyp =iparg(38,ng)
109C---
110 gbuf => elbuf_tab(ng)%GBUF
111C---
112 nft =iparg(3,ng)
113!
114 DO i=1,6
115 jj(i) = nel*(i-1)
116 ENDDO
117
118 value(1:3) = zero
119 DO i=1,nel
120 is_written_value(i) = 0
121 ENDDO
122c
123 IF (ity == 4) offset = 0
124 IF (ity == 5) offset = numelt
125 IF (ity == 6) offset = numelt+numelp
126c
127 DO i=1,nel
128 IF (ity == 4) THEN
129 id_elem(offset+nft+i) = ixt(nixt,nft+i)
130 ity_elem(offset+nft+i) = 4
131 IF( h3d_part(ipartt(nft+i)) == 1) iok_part(i) = 1
132 ELSEIF (ity == 5) THEN
133 id_elem(offset+nft+i) = ixp(nixp,nft+i)
134 ity_elem(offset+nft+i) = 5
135 IF( h3d_part(ipartp(nft+i)) == 1) iok_part(i) = 1
136 ELSEIF (ity == 6) THEN
137 id_elem(offset+nft+i) = ixr(nixr,nft+i)
138 ity_elem(offset+nft+i) = 6
139 IF( h3d_part(ipartr(nft+i)) == 1) iok_part(i) = 1
140 ENDIF
141 ENDDO
142
143 IF(ity==4 .OR. ity==5 .OR. ity==6)THEN
144 DO i=1,nel
145 oned_vector(1:3,offset+nft+i) = zero ! Default = zero in all cases !
146 ENDDO
147 ENDIF
148C-----------------------------------------------
149C TRUSS
150C-----------------------------------------------
151 IF(ity==4)THEN
152C--------------------------------------------------
153 IF (keyword == 'FINT') THEN
154C--------------------------------------------------
155 DO i=1,nel
156 value(1) = tors(1,offset+nft+i)
157 value(2) = tors(2,offset+nft+i)
158 value(3) = tors(3,offset+nft+i)
159 CALL h3d_write_vector(iok_part,is_written_oned,oned_vector,i,offset,nft,
160 . VALUE)
161 ENDDO
162C--------------------------------------------------
163c ELSEIF (KEYWORD == '') THEN
164C--------------------------------------------------
165c DO I=1,NEL
166c VALUE(1) =
167c VALUE(2) =
168c VALUE(3) =
169c CALL H3D_WRITE_VECTOR(IOK_PART,IS_WRITTEN_ONED,NODAL_VECTOR,I,0,0,
170c . VALUE)
171c ENDDO
172 ENDIF
173C-----------------------------------------------
174C POUTRES
175C-----------------------------------------------
176 ELSEIF(ity==5)THEN
177C--------------------------------------------------
178 IF (keyword == 'FINT') THEN
179C--------------------------------------------------
180 DO i=1,nel
181 value(1) = tors(1,offset+nft+i)
182 value(2) = tors(2,offset+nft+i)
183 value(3) = tors(3,offset+nft+i)
184 CALL h3d_write_vector(iok_part,is_written_oned,oned_vector,i,offset,nft,
185 . VALUE)
186 ENDDO
187C--------------------------------------------------
188c ELSEIF (KEYWORD == '') THEN
189C--------------------------------------------------
190c DO I=1,NEL
191c VALUE(1) =
192c VALUE(2) =
193c VALUE(3) =
194c CALL H3D_WRITE_VECTOR(IOK_PART,IS_WRITTEN_ONED,NODAL_VECTOR,I,0,0,
195c . VALUE)
196c ENDDO
197 ENDIF
198C-----------------------------------------------
199C RESSORTS
200C-----------------------------------------------
201 ELSEIF(ity==6)THEN
202C--------------------------------------------------
203 IF (keyword == 'FINT') THEN
204C--------------------------------------------------
205 DO i=1,nel
206 value(1) = tors(1,offset+nft+i)
207 value(2) = tors(2,offset+nft+i)
208 value(3) = tors(3,offset+nft+i)
209 CALL h3d_write_vector(iok_part,is_written_oned,oned_vector,i,offset,nft,
210 . VALUE)
211 ENDDO
212C--------------------------------------------------
213c ELSEIF (KEYWORD == '') THEN
214C--------------------------------------------------
215c DO I=1,NEL
216c VALUE(1) =
217c VALUE(2) =
218c VALUE(3) =
219c CALL H3D_WRITE_VECTOR(IOK_PART,IS_WRITTEN_ONED,NODAL_VECTOR,I,0,0,
220c . VALUE)
221c ENDDO
222 ENDIF
223 ENDIF
224 ENDDO
225
226 RETURN
227 END
#define my_real
Definition cppsort.cpp:32
subroutine genh3d(timers, x, d, v, a, bufel, ixs, ixq, ixc, ixt, ixp, ixr, ixtg, swaft, smas, sxnorm, siad, iparg, pm, geo, ms, sinvert, cont, smater, icut, skew, xcut, fint, itab, sel2fa, fext, fopt, anin, lpby, npby, nstrf, rwbuf, nprw, tani, elbuf_tab, mat_param, dd_iad, weight, eani, ipart, cluster, iparts, ipartq, ipartc, ipartt, ipartp, ipartr, ipartur, iparttg, rby, swa4, tors, nom_opt, bufsf, idata, rdata, siadg, bufmat, bufgeo, kxx, ixx, ipartx, suix, sxusr, snfacptx, sixedge, sixfacet, sixsolid, snumx1, snumx2, snumx3, soffx1, soffx2, soffx3, smass1, smass2, smass3, sfunc1, sfunc2, sfunc3, kxsp, ixsp, nod2sp, ipartsp, spbuf, ixs10, ixs20, ixs16, vr, monvol, volmon, ipm, igeo, nodglob, iad_elem, fr_elem, fr_sec, fr_rby2, iad_rby2, fr_wall, iflow, rflow, fncont, ftcont, temp, thke, err_thk_sh4, err_thk_sh3, diag_sms, ipari, fncont2, dr, ale_connect, irbe2, irbe3, lrbe2, lrbe3, fr_rbe2, fr_rbe3m, iad_rbe2, dxancg, nod_pxfem, iel_pxfem, zi_ply, vgaz, fcontg, fncontg, ftcontg, fanreac, inod_crk, iel_crk, elcutc, iadc_crk, pdama2, res_sms, weight_md, nodglobxfe, nodedge, fcluster, mcluster, xfem_tab, w, nv46, ipartig3d, kxig3d, ixig3d, sig3dsolid, knot, wige, nercvois, nesdvois, lercvois, lesdvois, crkedge, indx_crk, xedge4n, xedge3n, stack, sph2sol, stifn, stifr, igrnod, sh4tree, sh3tree, h3d_data, multi_fvm, subset, pskids, tag_skins6, tf, npf, fcont_max, mds_matid, fncontp2, ftcontp2, ibcl, iloadp, lloadp, fac, sensors, tagncont, loadp_hyd_inter, xframe, forc, ar, csefric, csefricg, csefric_stamp, csefricg_stamp, table, iframe, loads, drape_sh4n, drape_sh3n, drapeg, x_c, glob_therm, pblast)
Definition genh3d.F:212
subroutine h3d_oned_vector(elbuf_tab, ifunc, iparg, geo, ixt, ixp, ixr, pm, anim, oned_vector, id_elem, ity_elem, info1, info2, is_written_oned, ipartt, ipartp, ipartr, h3d_part, keyword, x, d, tors)
subroutine h3d_write_vector(iok_part, is_written, vector, i, offset, nft, value)
subroutine area(d1, x, x2, y, y2, eint, stif0)
for(i8=*sizetab-1;i8 >=0;i8--)
integer, parameter ncharline100