OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
check_ale_comm.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!|| check_ale_comm ../engine/source/ale/check_ale_comm.F
25!||--- called by ------------------------------------------------------
26!|| resol ../engine/source/engine/resol.F
27!||--- calls -----------------------------------------------------
28!||--- uses -----------------------------------------------------
29!|| elbufdef_mod ../common_source/modules/mat_elem/elbufdef_mod.F90
30!|| spmd_mod ../engine/source/mpi/spmd_mod.F90
31!||====================================================================
32 SUBROUTINE check_ale_comm(IPARG_L,ELBUF_TAB,GLOBAL_ACTIVE_ALE_ELEMENT,ITHERM)
33!$COMMENT
34! CHECK_ALE_COMM description
35! CHECK_ALE_COMM checks if all ALE elements are deactivated to
36! skip ALE solver
37! CHECK_ALE_COMM organization
38!$ENDCOMMENT
39 USE elbufdef_mod
40 USE spmd_mod
41C-----------------------------------------------
42C I m p l i c i t T y p e s
43C-----------------------------------------------
44#include "implicit_f.inc"
45C-----------------------------------------------
46C MPI
47C-----------------------------------------------
48#include "spmd.inc"
49C-----------------------------------------------
50C G l o b a l P a r a m e t e r s
51C-----------------------------------------------
52#include "com01_c.inc"
53#include "param_c.inc"
54C-----------------------------------------------
55C C o m m o n B l o c k s
56C-----------------------------------------------
57
58C-----------------------------------------------
59C D u m m y A r g u m e n t s
60C-----------------------------------------------
61 LOGICAL, INTENT(INOUT) :: GLOBAL_ACTIVE_ALE_ELEMENT
62 INTEGER, DIMENSION(NPARG,NGROUP), INTENT(IN) :: IPARG_L
63 INTEGER, INTENT(IN) :: ITHERM
64 TYPE(elbuf_struct_), DIMENSION(NGROUP), INTENT(IN) :: ELBUF_TAB
65C-----------------------------------------------
66C L o c a l V a r i a b l e s
67C-----------------------------------------------
68 LOGICAL :: ACTIVE_ALE_ELEMENT
69 INTEGER :: NG,I,NFT
70 INTEGER :: FIRST,LAST
71 INTEGER :: ITY,MTN,JEUL
72 my_real :: off_value
73#ifdef MPI
74 INTEGER :: IERROR
75#endif
76C-----------------------------------------------
77 ! ---------------------------------
78 IF(iale+ieuler+itherm /= 0) THEN
79 active_ale_element = .false.
80 ! -------------------
81 ! loop over the element groups to find the deactivated ALE elements
82 DO ng=1,ngroup
83 ity = iparg_l(5,ng)
84 mtn = iparg_l(1,ng)
85 IF(ity == 1 .OR. ity == 2)THEN
86 jeul = iparg_l(11,ng)
87 ELSEIF (mtn == 151 .AND. ity == 7) THEN
88 jeul = iparg_l(11,ng)
89 ELSE
90 jeul = 0
91 END IF
92 IF(iparg_l(7,ng)+jeul == 0)cycle
93 first = 1
94 last = iparg_l(2,ng)
95 nft = iparg_l(3,ng)
96 DO i=first,last
97 off_value = elbuf_tab(ng)%GBUF%OFF(i)
98 IF(off_value /= zero) THEN
99 active_ale_element = .true.
100 ENDIF
101 ENDDO
102 ENDDO
103 ! -------------------
104
105 IF(nspmd>1) THEN
106#ifdef MPI
107 CALL mpi_allreduce(active_ale_element,global_active_ale_element,1,mpi_logical,mpi_lor,spmd_comm_world,ierror)
108#endif
109 ELSE
110 global_active_ale_element = active_ale_element
111 ENDIF
112 ELSE
113 global_active_ale_element = .true.
114 ENDIF
115 ! ---------------------------------
116
117 RETURN
118 END SUBROUTINE check_ale_comm
subroutine check_ale_comm(iparg_l, elbuf_tab, global_active_ale_element, itherm)
#define my_real
Definition cppsort.cpp:32
subroutine mpi_allreduce(sendbuf, recvbuf, cnt, datatype, operation, comm, ierr)
Definition mpi.f:103