OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
spmd_h3d_quad_off.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_quad_off ../engine/source/output/h3d/spmd/spmd_h3d_quad_off.F
25!||--- called by ------------------------------------------------------
26!|| genh3d ../engine/source/output/h3d/h3d_results/genh3d.F
27!||--- uses -----------------------------------------------------
28!|| elbufdef_mod ../common_source/modules/mat_elem/elbufdef_mod.f90
29!||====================================================================
30 SUBROUTINE h3d_quad_off(ELBUF_TAB, IPARG, IXQ, QUAD_SCALAR, ID_ELEM,
31 . IPART , IPARTQ)
32C----------------------------------------------
33C M o d u l e s
34C-----------------------------------------------
35 USE elbufdef_mod
36C-----------------------------------------------
37C I m p l i c i t T y p e s
38C-----------------------------------------------
39#include "implicit_f.inc"
40C-----------------------------------------------
41C C o m m o n B l o c k s
42C-----------------------------------------------
43#include "com01_c.inc"
44#include "com04_c.inc"
45#include "param_c.inc"
46#include "scr17_c.inc"
47C-----------------------------------------------
48C D u m m y A r g u m e n t s
49C-----------------------------------------------
50 TYPE (ELBUF_STRUCT_), TARGET, DIMENSION(NGROUP), INTENT(IN) :: ELBUF_TAB
51 INTEGER, INTENT(IN) :: IPARG(NPARG,NGROUP),IXQ(NIXQ,NUMELQ),IPART(LIPART1,NPART+NTHPART)
52 INTEGER, INTENT(IN) :: IPARTQ(NUMELQ)
53 INTEGER, INTENT(INOUT) :: ID_ELEM(NUMELQ)
54 my_real, INTENT(INOUT) :: quad_scalar(numelq)
55
56C-----------------------------------------------
57C L O C A L V A R I A B L E S
58C-----------------------------------------------
59 INTEGER ITY,MLW,NEL,NFT,NG,I
60C-----------------------------------------------
61c
62 DO ng=1,ngroup
63 mlw =iparg(1,ng)
64 nel =iparg(2,ng)
65 ity =iparg(5,ng)
66 nft =iparg(3,ng)
67c
68 IF(ity == 2)THEN
69 DO i=1,nel
70 id_elem(nft+i) = ixq(nixq,nft+i)
71 ENDDO
72 ENDIF
73c
74 IF(ity == 2 )THEN
75 IF(mlw == 0 .OR. mlw == 13)THEN
76 DO i=1,nel
77 quad_scalar(nft+i) = one
78 ENDDO
79 ELSE
80 DO i=1,nel
81 IF(ipart(10,ipartq(nft+i)) /=0 .AND. nint(min(elbuf_tab(ng)%GBUF%OFF(i),one)) /= one) THEN
82 quad_scalar(nft+i) = zero
83 ELSE
84 quad_scalar(nft+i) = nint(min(elbuf_tab(ng)%GBUF%OFF(i),one))
85 ENDIF
86 ENDDO
87 ENDIF
88 ENDIF
89 ENDDO
90 RETURN
91 END
#define my_real
Definition cppsort.cpp:32
#define min(a, b)
Definition macros.h:20
subroutine h3d_quad_off(elbuf_tab, iparg, ixq, quad_scalar, id_elem, ipart, ipartq)