OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
i25gap3.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!|| i25gap3 ../engine/source/interfaces/int25/i25gap3.F
25!||--- called by ------------------------------------------------------
26!|| i25main_gap ../engine/source/interfaces/int25/i25main_gap.F
27!||--- calls -----------------------------------------------------
28!|| my_barrier ../engine/source/system/machine.F
29!||====================================================================
30 SUBROUTINE i25gap3(
31 1 ITASK,
32 2 NRTM ,IRECT ,GAP_NM ,GAP_M ,
33 3 NMN ,MSR ,GAPN_M ,
34 4 GAPMAX_M ,GAPSCALE ,MSEGTYP , THKNOD,
35 5 GAPMSAV, MAXDGAP_G)
36C-----------------------------------------------
37C I m p l i c i t T y p e s
38C-----------------------------------------------
39#include "implicit_f.inc"
40#include "comlock.inc"
41C-----------------------------------------------
42C C o m m o n B l o c k s
43C-----------------------------------------------
44#include "com04_c.inc"
45#include "task_c.inc"
46C-----------------------------------------------
47C D u m m y A r g u m e n t s
48C-----------------------------------------------
49 INTEGER NRTM,IRECT(4,*),
50 . MSR(*),NMN,MSEGTYP(*),ITASK
51C REAL
52 my_real
53 . GAP_NM(4,*),GAP_M(*), GAPMSAV(*), THKNOD(NUMNOD),
54 . gapn_m(*),gapmax_m, gapscale, maxdgap_g
55C-----------------------------------------------
56C L o c a l V a r i a b l e s
57C-----------------------------------------------
58 INTEGER I,J,K,IW,I1,I2,I3,MG,M,IP,IGTYP,
59 . NMNF,NMNL,NRTMF,NRTML,IERROR
60 my_real,
61 . DIMENSION(:), ALLOCATABLE :: WA
62 my_real MAXDGAP_L
63 SAVE wa
64C-----------------------------------------------
65C S o u r c e L i n e s
66C-----------------------------------------------
67 ALLOCATE(wa(numnod),stat=ierror)
68 nmnf = 1 + itask*nmn / nthread
69 nmnl = (itask+1)*nmn / nthread
70 nrtmf = 1 + itask * nrtm / nthread
71 nrtml = (itask+1) * nrtm / nthread
72 maxdgap_l = -ep30
73C------------------------------------
74C GAP_S = Secnds nodes gap [NSN]
75C GAPN_M = gap for each node on main [NMN]
76C GAP_NM = gap of each node on each main segment [4*NRTM]
77C GAP_M = for each main segment, max of gap of its connected nodes [NRTM]
78
79#include "vectorize.inc"
80 DO i=nmnf,nmnl
81 m = msr(i)
82 wa(m)=half*gapscale*thknod(m)
83 END DO
84C
85 CALL my_barrier
86C
87!$OMP SINGLE
88#include "vectorize.inc"
89 DO i=1,nrtm
90 IF (msegtyp(i)==0) THEN
91 DO j=1,4
92 m=irect(j,i)
93 wa(m) = zero
94 END DO
95 END IF
96 END DO
97!$OMP END SINGLE
98C
99#include "vectorize.inc"
100 DO i=nmnf,nmnl
101 m = msr(i)
102 wa(m) = min(wa(m),gapmax_m)
103 gapn_m(i) = wa(m)
104 END DO
105C
106 CALL my_barrier
107C
108#include "vectorize.inc"
109 DO i=nrtmf,nrtml
110 gap_m(i) = zero
111 DO j=1,4
112 m=irect(j,i)
113 gap_nm(j,i)=wa(m)
114 gap_m(i) = max(gap_m(i),wa(m))
115 END DO
116 END DO
117C
118#include "vectorize.inc"
119C calculate the maximum change in the gap, to be used in sorting criteria
120 DO i=nrtmf,nrtml
121 maxdgap_l = max(maxdgap_l,gap_m(i)-gapmsav(i))
122 END DO
123C
124 CALL my_barrier
125C
126#include "lockon.inc"
127C obtain the max dgap for all
128 maxdgap_g = max(maxdgap_l,maxdgap_g)
129#include "lockoff.inc"
130
131 RETURN
132 END
133C
subroutine i25gap3(itask, nrtm, irect, gap_nm, gap_m, nmn, msr, gapn_m, gapmax_m, gapscale, msegtyp, thknod, gapmsav, maxdgap_g)
Definition i25gap3.F:36
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21
subroutine my_barrier
Definition machine.F:31