OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
check_skew.F File Reference
#include "implicit_f.inc"
#include "tabsiz_c.inc"
#include "com01_c.inc"
#include "com04_c.inc"
#include "param_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine check_skew (ixr, igeo, iskn, cep, iskwp, nskwp, tag_skn, multiple_skew, r_skew, ipm, offset)

Function/Subroutine Documentation

◆ check_skew()

subroutine check_skew ( integer, dimension(nixr,numelr), intent(in) ixr,
integer, dimension(npropgi,numgeo), intent(in) igeo,
integer, dimension(liskn,siskwn/liskn), intent(in) iskn,
integer, dimension(scep), intent(in) cep,
integer, dimension(numskw+1), intent(inout) iskwp,
integer, dimension(nspmd), intent(inout) nskwp,
integer, dimension(numskw+nsubmod+1), intent(inout) tag_skn,
type(plist_skew_), dimension(numskw+1), intent(inout) multiple_skew,
integer, dimension(numelr), intent(inout) r_skew,
integer, dimension(npropmi,nummat), intent(in) ipm,
integer offset )

Definition at line 33 of file check_skew.F.

35C-----------------------------------------------
36C M o d u l e s
37C-----------------------------------------------
38 USE skew_mod
39 USE submodel_mod , ONLY : nsubmod
40C-----------------------------------------------
41C I m p l i c i t T y p e s
42C-----------------------------------------------
43#include "implicit_f.inc"
44C-----------------------------------------------
45C C o m m o n B l o c k s
46C-----------------------------------------------
47#include "tabsiz_c.inc"
48#include "com01_c.inc"
49#include "com04_c.inc"
50#include "param_c.inc"
51C-----------------------------------------------
52C D u m m y A r g u m e n t s
53C-----------------------------------------------
54 INTEGER, INTENT(INOUT) :: NSKWP(NSPMD),R_SKEW(NUMELR)
55 INTEGER, DIMENSION(NUMSKW+NSUBMOD+1), INTENT(INOUT) :: TAG_SKN
56 INTEGER, DIMENSION(SCEP), INTENT(IN) :: CEP
57 INTEGER, DIMENSION(NUMSKW+1), INTENT(INOUT) :: ISKWP
58 INTEGER, DIMENSION(NIXR,NUMELR), INTENT(IN) :: IXR
59 INTEGER, DIMENSION(NPROPGI,NUMGEO), INTENT(IN) :: IGEO
60 INTEGER, DIMENSION(LISKN,SISKWN/LISKN), INTENT(IN) :: ISKN
61 INTEGER, DIMENSION(NPROPMI,NUMMAT), INTENT(IN) :: IPM
62 TYPE(PLIST_SKEW_), DIMENSION(NUMSKW+1), INTENT(INOUT) :: MULTIPLE_SKEW
63 INTEGER :: OFFSET
64! -*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-**-*-*-*-*-*-*-*-*-*-*-*-*
65! NSKWP : integer ; dimension = NSPMD
66! number of skew per processor
67! TAG_SKN : integer ; dimension=NUMSKW+NSUBMOD+1
68! tag array --> tag the i SKEW if a SPRING uses it
69! tag array=0 --> the SKEW is not used by a SPRING
70! tag array=1 --> the SKEW is used by one SPRING
71! tag array>1 --> the SKEW is used by several SPRING
72! tag array <0 --> the SKEW is used by several options (has to be duplicated to all domains that have the nodes)
73! CEP : integer ; dimension=NUMNOD
74! gives the ID processor of the current i node
75! ISKWP : integer ; dimension=NUMSKW+1
76! gives the ID processir of the current i SKEW
77! ISKWP < 0 --> the SKEW is local on a processor
78! and we don't need to communicate the data
79! ISKWP > 0 --> the SKEW is global and the data must be
80! communicated
81! IXR : integer ; dimension=NIXR*number of SPRING
82! SPRING array
83! IGEO : integer ; dimension=NPROPGI*number of /PROP
84! PROP array
85! ISKN : integer ; dimension=LISKN*number of SKEW
86! SKEW array
87! MULTIPLE_SKEW : SKEW_TYPE ; dimension=NUMSKW+1
88! MULTIPLE_SKEW(I)%PLIST(:) is a list of processor
89! where the SKEW is stuck
90! OFFSET :: integer, offset to point to the good place in CEP array
91! -*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-**-*-*-*-*-*-*-*-*-*-*-*-*
92
93C-----------------------------------------------
94C L o c a l V a r i a b l e s
95C-----------------------------------------------
96 INTEGER :: I,J,II,NN
97 INTEGER :: NUMBER_SKEW_SP,SPRING_TYPE
98 INTEGER :: N1,N2,N3,IMAIN,SUM_NI,SIZE_SKEW,MAT_TYPE
99 INTEGER :: NL, ISKEW, NB
100 INTEGER, DIMENSION(:), ALLOCATABLE :: SKEW_PER_SP,LOCAL_P,P_SKEW
101 INTEGER, DIMENSION(NSPMD) :: PROC_SKEW
102C-----------------------------------------------
103C E x t e r n a l F u n c t i o n s
104C-----------------------------------------------
105C=======================================================================
106!$COMMENT
107! CHECK_SKEW description
108! CHECK_SKEW sticks a SKEW on a given processor in order to reduce
109! the SKEW communication in the engine.
110! A SKEW can be linked to a SPRING --> in this case, the SKEW is
111! stuck on the local SPRING processor
112! If a SKEW is used by several SPRING, the SKEW is stuck on each
113! processors that need it
114!
115! CHECK_SKEW organization :
116! - link every SPRING with theirs SKEW
117! - if several SPRING use a same SKEW, allocate MULTIPLE_SKEW(I)%PLIST
118! - stick a SKEW on a given processor, count the number of SKEW per
119! processor, initialize the MULTIPLE_SKEW(I)%PLIST array
120! - count the number of SKEW per processor in the case of multiple
121! SPRING per SKEW
122!$ENDCOMMENT
123C
124! compute adhoc size for local arrays
125 number_skew_sp = 0
126 tag_skn(1:numskw+nsubmod+1) = -1
127 nb = 0
128 DO i = 1,numskw
129 ! The optimization of restricting a skew to the domains having the corresponding spring nodes
130 ! works only for skew referenced by only one options
131 CALL hm_entity_reference_number("/SKEW",len_trim("/SKEW"),iskn(4,i+1),nb)
132 IF(nb == 1) tag_skn(i+1) = 0
133 ENDDO
134
135
136 DO i=1,numelr
137 spring_type = igeo( 11,ixr(1,i) )
138 mat_type = 0
139 IF (ixr(5,i) > 0) mat_type = ipm(2,ixr(5,i))
140C
141 IF (r_skew(i) > 1) THEN
142 IF( tag_skn(r_skew(i)) >= 0 ) THEN
143 IF(spring_type==8 .OR. (spring_type== 23 .AND. mat_type == 108)) number_skew_sp = number_skew_sp + 1
144 ENDIF
145 ENDIF
146C
147 IF (igeo(2,ixr(1,i) )>1) THEN
148 IF( tag_skn( igeo(2,ixr(1,i))) >= 0 ) THEN
149 IF(spring_type==8 .OR. spring_type==13 .OR. spring_type== 23) number_skew_sp = number_skew_sp + 1
150 ENDIF
151 ENDIF
152 ENDDO
153
154! allocation and initialization of local array
155 ALLOCATE(skew_per_sp(number_skew_sp))
156 ALLOCATE(local_p(number_skew_sp))
157
158
159
160
161 skew_per_sp(1:number_skew_sp) = 0
162 local_p(1:number_skew_sp) = 0
163 number_skew_sp = 0
164
165! link between SPRING and SKEW (only for SPRING type =8,13 or 23)
166 DO i=1,numelr
167 spring_type = igeo( 11,ixr(1,i) )
168 mat_type = 0
169 IF (ixr(5,i) > 0) mat_type = ipm(2,ixr(5,i))
170C
171 IF (r_skew(i) > 1) THEN
172 IF( tag_skn(r_skew(i)) >= 0) THEN
173 IF(spring_type==8 .OR. (spring_type== 23 .AND. mat_type == 108)) THEN
174 number_skew_sp = number_skew_sp + 1
175 skew_per_sp( number_skew_sp ) = r_skew(i)
176 local_p(number_skew_sp) = cep(offset+i)+1
177 tag_skn( r_skew(i) ) = tag_skn( r_skew(i) ) + 1
178 ENDIF
179 ENDIF
180 ENDIF
181C
182 IF (igeo( 2,ixr(1,i) )>1) THEN
183 IF( tag_skn(igeo(2,ixr(1,i))) >=0 ) THEN
184 IF(spring_type==8 .OR. spring_type==13 .OR. spring_type== 23) THEN
185 number_skew_sp = number_skew_sp + 1
186 skew_per_sp( number_skew_sp ) = igeo( 2,ixr(1,i) )
187 local_p(number_skew_sp) = cep(offset+i)+1
188 tag_skn( igeo(2,ixr(1,i)) ) = tag_skn( igeo(2,ixr(1,i)) ) + 1
189 ENDIF
190 ENDIF
191 ENDIF
192 ENDDO
193
194! allocation of MULTIPLE_SKEW
195 DO i=1,numskw+1
196 size_skew = tag_skn(i)
197 IF(size_skew>1) THEN
198 IF(.NOT.ALLOCATED(multiple_skew(i)%PLIST)) ALLOCATE( multiple_skew(i)%PLIST(size_skew) )
199 multiple_skew(i)%PLIST(1:size_skew) = 0
200 ENDIF
201 ENDDO
202
203 ALLOCATE(p_skew(numskw+1))
204 p_skew(1:numskw+1) = 0
205
206! stick a SKEW on a given processor
207 DO j=1,number_skew_sp
208 i = skew_per_sp(j)
209 imain = local_p(j)
210 n1=iskn(1,i)
211 n2=iskn(2,i)
212 n3=iskn(3,i)
213 sum_ni = n1+n2+n3
214 IF(sum_ni/=0) THEN
215
216 CALL ifrontplus(n1,imain)
217 CALL ifrontplus(n2,imain)
218 CALL ifrontplus(n3,imain)
219 IF(iskwp(i)==0) iskwp(i) = -imain
220 IF(tag_skn(i)>1) THEN
221 p_skew(i) = p_skew(i) + 1
222 multiple_skew(i)%PLIST(p_skew(i)) = imain
223 ELSE
224 nskwp(imain) = nskwp(imain) + 1
225 ENDIF
226 ENDIF
227 ENDDO
228
229! count and add the number of SKEW per processor in the case of multiple SPRING per SKEW
230 DO i=1,numskw+1
231 size_skew = tag_skn(i)
232 IF(size_skew>1) THEN
233 proc_skew(1:nspmd) = 0
234 DO ii=1,size_skew
235 imain = multiple_skew(i)%PLIST(ii)
236 IF(imain>0) proc_skew(imain) = proc_skew(imain) + 1
237 ENDDO
238 DO ii=1,nspmd
239 IF(proc_skew(ii)>0) nskwp(ii) = nskwp(ii) + 1
240 ENDDO
241 ENDIF
242 ENDDO
243
244! deallocation of local arrais
245 DEALLOCATE(skew_per_sp,local_p)
246 DEALLOCATE(p_skew)
247
248 RETURN
subroutine ifrontplus(n, p)
Definition frontplus.F:100
subroutine hm_entity_reference_number(name, sname, id, ref_number)
integer nsubmod