OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
fcont_max_output.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!|| fcont_max_output ../engine/source/output/h3d/h3d_results/fcont_max_output.F
25!||--- called by ------------------------------------------------------
26!|| sortie_main ../engine/source/output/sortie_main.F
27!||--- calls -----------------------------------------------------
28!|| spmd_h3d_sum_r_nodal_21 ../engine/source/output/h3d/spmd/spmd_h3d_gather_r_node.F
29!||====================================================================
30 SUBROUTINE fcont_max_output(CONT,FCONTG,NODGLOB,FCONT_MAX,WEIGHT)
31C-----------------------------s------------------
32C I m p l i c i t T y p e s
33C-----------------------------------------------
34#include "implicit_f.inc"
35C-----------------------------------------------
36C C o m m o n B l o c k s
37C-----------------------------------------------
38#include "task_c.inc"
39#include "com01_c.inc"
40#include "com04_c.inc"
41#include "spmd_c.inc"
42#include "intstamp_c.inc"
43C-----------------------------------------------
44C D u m m y A r g u m e n t s
45C-----------------------------------------------
46 INTEGER NODGLOB(*),WEIGHT(*)
48 . cont(3,*),fcontg(3,*),fcont_max(3,*)
49 my_real fold, fnew, fmax
50 INTEGER I,K,N
52 . , DIMENSION(:,:), ALLOCATABLE :: fcont_tmp,fcont_tmp_p
53C-----------------------------------------------
54
55 IF(nintstamp == 0) THEN
56 DO n=1,numnod
57 IF(weight(n) == 1) THEN
58 fnew = cont(1,n)**2 + cont(2,n)**2 +cont(3,n)**2
59 fold = fcont_max(1,n)**2 + fcont_max(2,n)**2 +fcont_max(3,n)**2
60 fmax = max(fnew,fold)
61 IF(fnew > fold) THEN
62 fcont_max(1:3,n) = cont(1:3,n)
63 ENDIF
64 ELSE
65 cont(1:3,n) = zero
66 ENDIF
67 ENDDO
68 ELSE
69
70 ALLOCATE(fcont_tmp(3,numnod))
71 ALLOCATE(fcont_tmp_p(3,numnodg))
72
73 DO i=1,numnod
74 k=nodglob(i)
75 fcont_tmp(1,i) = cont(1,i) + fcontg(1,k)
76 fcont_tmp(2,i) = cont(2,i) + fcontg(2,k)
77 fcont_tmp(3,i) = cont(3,i) + fcontg(3,k)
78 ENDDO
79
80 IF(nspmd > 1 ) THEN
81 CALL spmd_h3d_sum_r_nodal_21(nodglob,fcont_tmp,3*numnod,fcont_tmp_p,3*numnodg,fcontg)
82 ENDIF
83
84 IF(nspmd > 1) THEN
85 IF(ispmd == 0 ) THEN
86 DO n=1,numnodg
87 fnew = fcont_tmp_p(1,n)**2 + fcont_tmp_p(2,n)**2 +fcont_tmp_p(3,n)**2
88 fold = fcont_max(1,n)**2 + fcont_max(2,n)**2 +fcont_max(3,n)**2
89 fmax = max(fnew,fold)
90 IF(fnew > fold) THEN
91 fcont_max(1:3,n) = fcont_tmp_p(1:3,n)
92 ENDIF
93 ENDDO
94 ENDIF
95 ELSE
96 DO n=1,numnod
97 IF(weight(n) /= 1) cycle
98 fnew = fcont_tmp(1,n)**2 + fcont_tmp(2,n)**2 +fcont_tmp(3,n)**2
99 fold = fcont_max(1,n)**2 + fcont_max(2,n)**2 +fcont_max(3,n)**2
100 fmax = max(fnew,fold)
101 IF(fnew > fold) THEN
102 fcont_max(1:3,n) = fcont_tmp(1:3,n)
103 ENDIF
104 ENDDO
105 ENDIF
106 DEALLOCATE( fcont_tmp_p, fcont_tmp)
107 ENDIF
108
109 RETURN
110 END
#define my_real
Definition cppsort.cpp:32
subroutine fcont_max_output(cont, fcontg, nodglob, fcont_max, weight)
#define max(a, b)
Definition macros.h:21
subroutine spmd_h3d_sum_r_nodal_21(nodglob, v, len, vp0, lenp0, vg21)