OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
s_user.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!|| s_user ../engine/source/output/sty/s_user.F
25!||--- called by ------------------------------------------------------
26!|| outp_c_s ../engine/source/output/sty/outp_c_s.F
27!||--- uses -----------------------------------------------------
28!|| elbufdef_mod ../common_source/modules/mat_elem/elbufdef_mod.F90
29!||====================================================================
30 SUBROUTINE s_user(NBX,IMX,IHBE,NEL,NPT,MLW,IPM,IGEO, IXC,
31 . ITY,JJ,ELBUF_TAB,WA,NFT, FUNC,
32 . NLAY,NPTR,NPTS)
33C-----------------------------------------------
34C M o d u l e s
35C-----------------------------------------------
36 USE elbufdef_mod
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 "param_c.inc"
45C-----------------------------------------------
46C D u m m y A r g u m e n t s
47C-----------------------------------------------
48 INTEGER IHBE,NEL,NPT,JJ,MLW,ITY,NLAY,NPTR,NPTS,
49 .IXC(NIXC,*),IPM(NPROPMI,*),IGEO(NPROPGI,*)
51 . wa(*)
52 TYPE (ELBUF_STRUCT_) , TARGET :: ELBUF_TAB
53C-----------------------------------------------
54C L o c a l V a r i a b l e s
55C-----------------------------------------------
56 INTEGER I,J,K,II,I1,IPT,IL,IR,IS,IT,
57 . NUVAR,IGTYP,NFT, NBX, IMX,NPTT
59 . fac,aa,var(200),func(6)
60 TYPE(buf_mat_) ,POINTER :: MBUF
61C=======================================================================
62C QBAT----
63 IF (ity == 3 .AND. ihbe == 11) THEN
64 fac = fourth
65 ENDIF
66C DKT18----
67 IF (ity == 7 .AND. ihbe == 11) THEN
68 fac = third
69 ENDIF
70C------------------------
71C---QEPH:------
72 IF (ihbe == 23) THEN
73C---Transfer to QBAT------
74 ELSEIF (ihbe == 11) THEN ! QBAT,DKT18
75 IF (mlw == 29.OR.mlw == 30.OR.mlw == 31.OR.mlw>=33) THEN
76 nuvar = 0
77 DO i=1,nel
78 nuvar = max(nuvar,ipm(8,ixc(1,nft+1)))
79 ENDDO
80 igtyp = igeo(11,ixc(6,nft+1))
81 ENDIF
82c
83 ii = nbx - 19
84 i1 = (ii -1)*nel
85 DO i=1,nel
86 aa = zero
87 IF (mlw == 29.OR.mlw == 30.OR.mlw == 31.OR.mlw>=33) THEN
88c
89 IF (nlay > 1) THEN
90 it = 1
91 DO ipt=1,nlay
92 DO ir=1,nptr
93 DO is=1,npts
94 mbuf => elbuf_tab%BUFLY(ipt)%MAT(1,1,it)
95 var(ipt) = var(ipt) + mbuf%VAR(i1 + i )*fac
96 IF (var(ipt) >= aa) aa = var(ipt)
97 ENDDO
98 ENDDO
99 ENDDO
100 ELSE ! NLAY = 1
101 il = 1
102 nptt = elbuf_tab%NPTT
103 DO ipt=1,nptt
104 var(ipt) = zero
105 DO ir=1,nptr
106 DO is=1,npts
107 mbuf => elbuf_tab%BUFLY(il)%MAT(1,1,ipt)
108 var(ipt) = var(ipt) + mbuf%VAR(i1 + i )*fac
109 IF (var(ipt) >= aa) aa = var(ipt)
110 ENDDO
111 ENDDO
112 ENDDO
113 ENDIF ! NLAY
114c
115 IF(imx == 0)THEN
116 wa(jj +1) = var(iabs(npt)/2 + 1)
117 ELSE
118 wa(jj + 1) = aa
119 ENDIF
120 jj = jj + 1
121 ENDIF
122 ENDDO
123 ELSE ! IHBE == 11
124c error message------
125 ENDIF
126C-----------
127 RETURN
128 END
#define my_real
Definition cppsort.cpp:32
#define max(a, b)
Definition macros.h:21
subroutine s_user(nbx, imx, ihbe, nel, npt, mlw, ipm, igeo, ixc, ity, jj, elbuf_tab, wa, nft, func, nlay, nptr, npts)
Definition s_user.F:33