OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
h3d_oned_vector.F File Reference
#include "implicit_f.inc"
#include "mvsiz_p.inc"
#include "com01_c.inc"
#include "com04_c.inc"
#include "param_c.inc"

Go to the source code of this file.

Functions/Subroutines

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)

Function/Subroutine Documentation

◆ h3d_oned_vector()

subroutine h3d_oned_vector ( type (elbuf_struct_), dimension(ngroup), target elbuf_tab,
integer ifunc,
integer, dimension(nparg,*) iparg,
geo,
integer, dimension(nixt,*) ixt,
integer, dimension(nixp,*) ixp,
integer, dimension(nixr,*) ixr,
pm,
anim,
oned_vector,
integer, dimension(*) id_elem,
integer, dimension(*) ity_elem,
integer info1,
integer info2,
integer, dimension(*) is_written_oned,
integer, dimension(*) ipartt,
integer, dimension(*) ipartp,
integer, dimension(*) ipartr,
integer, dimension(*) h3d_part,
character(len=ncharline100) keyword,
x,
d,
tors )

Definition at line 33 of file h3d_oned_vector.F.

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
#define my_real
Definition cppsort.cpp:32
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