OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
split_cfd_solide.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!||====================================================================
25!|| split_cfd_solide ../starter/source/spmd/split_cfd_solide.F
26!||--- called by ------------------------------------------------------
27!|| lectur ../starter/source/starter/lectur.F
28!||--- calls -----------------------------------------------------
29!|| plist_ifront ../starter/source/spmd/node/ddtools.F
30!||--- uses -----------------------------------------------------
31!|| split_cfd_mod ../starter/share/modules1/split_cfd_mod.F
32!||====================================================================
33 SUBROUTINE split_cfd_solide(NUMELS,ALE_CONNECTIVITY,IXS,ALE_ELM,SIZE_ALE_ELM)
34!$COMMENT
35! SPLIT_CFD_SOLIDE description :
36! SPLIT_CFD_SOLIDE retains all the useful solid elements
37! for the splitting in DDSPLIT for each domain in order to
38! avoid a quadratic loop in DDSPLIT
39! SPLIT_CFD_SOLIDE organization :
40! - first allocation of ALE_ELM%SOL_ID array
41! - for each solid element, if a neighbouring element
42! is useful for the splitting, catch the processor list
43! - fill the ALE_ELM array and if the ALE_ELM size is not
44! sufficient, then increase the size
45!$ENDCOMMENT
46C-----------------------------------------------
47C M o d u l e s
48C-----------------------------------------------
51C-----------------------------------------------
52C I m p l i c i t T y p e s
53C-----------------------------------------------
54#include "implicit_f.inc"
55C-----------------------------------------------
56C C o m m o n B l o c k s
57C-----------------------------------------------
58#include "com01_c.inc"
59C-----------------------------------------------
60C D u m m y A r g u m e n t s
61C-----------------------------------------------
62 INTEGER, INTENT(IN) :: NUMELS
63 INTEGER, DIMENSION(NIXS,*), INTENT(IN) :: IXS
64 INTEGER, DIMENSION(NSPMD) :: SIZE_ALE_ELM
65 TYPE(split_cfd_type), DIMENSION(NSPMD), INTENT(INOUT) :: ALE_ELM
66 TYPE(t_ale_connectivity), INTENT(INOUT) :: ALE_CONNECTIVITY
67! -*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-**-*-*-*-*-*-*-*-*-*-*-*-*
68! NUMELS : integer ; number of solid element
69! NIXS : integer ; dimension of IXS array
70
71! IXS : integer ; dimension=NIXS,NUMELS ; property of solid element
72! SIZE_ALE_ELM : integer ; dimension=NSPMD ; size of ALE_ELM%SOL_ID array
73! ALE_ELM : split_cfd_type ; dimension=NSPMD ; solid element ID used
74! during the domain splitting (ALE part)
75! -*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-**-*-*-*-*-*-*-*-*-*-*-*-*
76C-----------------------------------------------
77C L o c a l V a r i a b l e s
78C-----------------------------------------------
79 LOGICAL, DIMENSION(NSPMD) :: BOOL
80 INTEGER :: I,J,K,L,N,NS,IAD1,LGTH
81 INTEGER :: SOLV,ISPMD,NBR_PROC,NEW_SIZE_II,MIN_SIZE
82 INTEGER, DIMENSION(NSPMD) :: ID_SPMD,II
83 INTEGER, DIMENSION(:), ALLOCATABLE :: TMP
84C ----------------------------------------
85
86 ! -----------------------------
87 ! allocation of ALE_ELM (overestimation of the size)
88 size_ale_elm(1:nspmd) = numels/nspmd+1
89 DO ispmd=1,nspmd
90 ALLOCATE( ale_elm(ispmd)%SOL_ID(size_ale_elm(ispmd)) )
91 ENDDO
92 ! -----------------------------
93 ii(1:nspmd) = 0
94 DO i=1,numels
95 ! -----------------------------
96 ! check if a neighbouring element is used
97 bool(1:nspmd)=.false.
98 iad1 = ale_connectivity%ee_connect%iad_connect(i)
99 lgth = ale_connectivity%ee_connect%iad_connect(i+1)-ale_connectivity%ee_connect%iad_connect(i)
100 DO j=1,8
101 ns = ixs(j+1,i)
102 DO k=1,lgth
103 solv = ale_connectivity%ee_connect%connected(iad1 + k - 1)
104 IF (solv>0) THEN
105 DO l=1,8
106 n = ixs(l+1,solv)
107 CALL plist_ifront(id_spmd,n,nbr_proc)
108 DO ispmd=1,nbr_proc
109 bool(id_spmd(ispmd)) = .true.
110 ENDDO
111 ENDDO
112 ENDIF
113 ENDDO
114 ENDDO
115 ! -----------------------------
116 ! fill the ALE_ELM array / increase the size
117 DO ispmd=1,nspmd
118 IF( bool(ispmd) ) THEN
119 ii(ispmd) = ii(ispmd) + 1
120 IF( ii(ispmd)>size_ale_elm(ispmd) ) THEN
121 ! need to check the size for small test, ie. when NUMELS < NSPMS
122 min_size=max(1,5* numels/ ( 4*nspmd ))
123 new_size_ii = size_ale_elm(ispmd) + min_size
124 ALLOCATE( tmp( new_size_ii ) )
125 tmp(1:size_ale_elm(ispmd)) = ale_elm(ispmd)%SOL_ID( 1:size_ale_elm(ispmd) )
126 CALL move_alloc(from=tmp,to=ale_elm(ispmd)%SOL_ID)
127 size_ale_elm(ispmd) = new_size_ii
128 ENDIF
129 ale_elm(ispmd)%SOL_ID(ii(ispmd)) = i
130 ENDIF
131 ENDDO
132 ! -----------------------------
133 ENDDO
134 ! -----------------------------
135
136 size_ale_elm(1:nspmd) = ii(1:nspmd)
137
138 RETURN
139 END SUBROUTINE split_cfd_solide
140
141
142
143!||====================================================================
144!|| deallocate_split_cfd_solide ../starter/source/spmd/split_cfd_solide.F
145!||--- called by ------------------------------------------------------
146!|| lectur ../starter/source/starter/lectur.F
147!||--- uses -----------------------------------------------------
148!|| split_cfd_mod ../starter/share/modules1/split_cfd_mod.F
149!||====================================================================
150 SUBROUTINE deallocate_split_cfd_solide(ALE_ELM)
151!$COMMENT
152! DEALLOCATE_SPLIT_CFD_SOLIDE description :
153! DEALLOCATE_SPLIT_CFD_SOLIDE deallocates the
154! ALE_ELM array
155! DEALLOCATE_SPLIT_CFD_SOLIDE organization :
156! - loop over NSPMD + deallocation
157!$ENDCOMMENT
158C-----------------------------------------------
159C M o d u l e s
160C-----------------------------------------------
161 USE split_cfd_mod
162C-----------------------------------------------
163C I m p l i c i t T y p e s
164C-----------------------------------------------
165#include "implicit_f.inc"
166C-----------------------------------------------
167C C o m m o n B l o c k s
168C-----------------------------------------------
169#include "com01_c.inc"
170C-----------------------------------------------
171C D u m m y A r g u m e n t s
172C-----------------------------------------------
173 TYPE(split_cfd_type), DIMENSION(NSPMD), INTENT(INOUT) :: ALE_ELM
174! -*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-**-*-*-*-*-*-*-*-*-*-*-*-*
175! ALE_ELM : split_cfd_type ; dimension=NSPMD ; solid element ID used
176! during the domain splitting (ALE part)
177! -*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-**-*-*-*-*-*-*-*-*-*-*-*-*
178C-----------------------------------------------
179C L o c a l V a r i a b l e s
180C-----------------------------------------------
181 INTEGER :: ISPMD
182C ----------------------------------------
183 DO ispmd=1,nspmd
184 IF( ALLOCATED(ale_elm(ispmd)%SOL_ID) ) DEALLOCATE( ale_elm(ispmd)%SOL_ID )
185 ENDDO
186 RETURN
187 END SUBROUTINE deallocate_split_cfd_solide
188
189
190
subroutine plist_ifront(tab, n, cpt)
Definition ddtools.F:153
#define max(a, b)
Definition macros.h:21
subroutine split_cfd_solide(numels, ale_connectivity, ixs, ale_elm, size_ale_elm)
subroutine deallocate_split_cfd_solide(ale_elm)