OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
w_dampvrel.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!|| w_dampvrel ../starter/source/restart/ddsplit/w_dampvrel.F
25!||--- called by ------------------------------------------------------
26!|| ddsplit ../starter/source/restart/ddsplit/ddsplit.F
27!||--- calls -----------------------------------------------------
28!|| nlocal ../starter/source/spmd/node/ddtools.F
29!||--- uses -----------------------------------------------------
30!||====================================================================
31 SUBROUTINE w_dampvrel(DAMPR,IGRNOD,IDAMP_VREL_L,NDAMP_VREL_L,LEN_IA,
32 . NGRNOD,NDAMP,NRDAMP,NSPMD)
33C-----------------------------------------------
34C M o d u l e s
35C-----------------------------------------------
36 USE groupdef_mod
37C---------------------------------------------
38C I m p l i c i t T y p e s
39C-----------------------------------------------
40#include "implicit_f.inc"
41C-----------------------------------------------
42C D u m m y A r g u m e n t s
43C-----------------------------------------------
44 INTEGER, INTENT(IN) :: NDAMP_VREL_L,NGRNOD,NDAMP,NRDAMP,NSPMD
45 INTEGER, INTENT(IN) :: IDAMP_VREL_L(NDAMP)
46 INTEGER, INTENT(INOUT) :: LEN_IA
47 my_real, INTENT(IN) :: dampr(nrdamp,ndamp)
48 TYPE (GROUP_),DIMENSION(NGRNOD),INTENT(IN) :: IGRNOD
49C-----------------------------------------------
50C E x t e r n a l F u n c t i o n s
51C-----------------------------------------------
52 INTEGER NLOCAL
53 EXTERNAL nlocal
54C-----------------------------------------------
55C L o c a l V a r i a b l e s
56C-----------------------------------------------
57 INTEGER I,J,IGR,PROC,PMAIN,CPT
58 INTEGER FR_DAMP_VREL(NSPMD+2,NDAMP_VREL_L),ID_DAMP_VREL(NDAMP_VREL_L)
59C-----------------------------------------------
60C
61 pmain = 1
62 cpt = 0
63 DO i=1,ndamp
64 IF (idamp_vrel_l(i) > 0) THEN
65 cpt = cpt+1
66 id_damp_vrel(cpt) = i
67 ENDIF
68 ENDDO
69C
70 fr_damp_vrel(1:nspmd+2,1:ndamp_vrel_l) = 0
71 DO i=1,ndamp_vrel_l
72 igr = nint(dampr(2,id_damp_vrel(i)))
73C-- Tag of procs having nodes in damping
74 DO proc = 1,nspmd
75 DO j = 1,igrnod(igr)%NENTITY
76 IF (nlocal(igrnod(igr)%ENTITY(j),proc)==1) THEN
77 fr_damp_vrel(proc,i) = 1
78 ENDIF
79 ENDDO
80 ENDDO
81C-- Find main proc for damping (smallest proc id)
82 DO proc = 1,nspmd
83 IF (fr_damp_vrel(proc,i) == 1) THEN
84 pmain = proc
85 exit
86 ENDIF
87 ENDDO
88 fr_damp_vrel(nspmd+1,i) = 0 ! Not used for now
89 fr_damp_vrel(nspmd+2,i) = pmain
90 ENDDO
91C
92 CALL write_i_c(id_damp_vrel,ndamp_vrel_l)
93 len_ia = len_ia + ndamp_vrel_l
94C
95 CALL write_i_c(fr_damp_vrel,ndamp_vrel_l*(nspmd+2))
96 len_ia = len_ia + ndamp_vrel_l*(nspmd+2)
97C
98! --------------------------------------
99 RETURN
100 END
#define my_real
Definition cppsort.cpp:32
subroutine w_dampvrel(dampr, igrnod, idamp_vrel_l, ndamp_vrel_l, len_ia, ngrnod, ndamp, nrdamp, nspmd)
Definition w_dampvrel.F:33
void write_i_c(int *w, int *len)