OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
write_joint.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!|| write_joint ../starter/source/constraints/general/cyl_joint/write_joint.F
25!||--- called by ------------------------------------------------------
26!|| ddsplit ../starter/source/restart/ddsplit/ddsplit.F
27!||--- calls -----------------------------------------------------
28!||--- uses -----------------------------------------------------
29!|| joint_mod ../starter/share/modules1/joint_mod.F
30!||====================================================================
31 SUBROUTINE write_joint(LJOINT,CEP,CEL,PROC,
32 + NODLOCAL,LJOINT_L,LEN_IA,NUMNOD_L)
33!$COMMENT
34! WRITE_JOINT description
35! write the joint structure
36!
37! WRITE_JOINT organization :
38!$ENDCOMMENT
39C-----------------------------------------------
40C M o d u l e s
41C-----------------------------------------------
42 USE joint_mod
43C-----------------------------------------------
44C I m p l i c i t T y p e s
45C-----------------------------------------------
46#include "implicit_f.inc"
47C-----------------------------------------------
48C C o m m o n B l o c k s
49C-----------------------------------------------
50#include "com04_c.inc"
51#include "com01_c.inc"
52C-----------------------------------------------
53C D u m m y A r g u m e n t s
54C-----------------------------------------------
55 INTEGER PROC, LJOINT_L, LEN_IA, NODLOCAL(*),
56 . ljoint(*), cep(*), cel(*),numnod_l
57C-----------------------------------------------
58C L o c a l V a r i a b l e s
59C-----------------------------------------------
60 INTEGER N,NN,K,J,P,I,NUMBER_MAIN_NODE,IS_SMS_AVAILABLE
61 INTEGER, DIMENSION(:), ALLOCATABLE :: BUF_W
62 INTEGER, DIMENSION(NSPMD) :: NB_NODE_WEIGHT
63 INTEGER, DIMENSION(2) :: MAIN_NODE
64 INTEGER, DIMENSION(:), ALLOCATABLE :: SECONDARY_NODE
65C
66 p = proc + 1
67 ! ----------------------
68 ! count the number of data in order to allocate the buffer
69 k = 0
70 DO n=1,njoint
71 IF(cyl_join(n)%NB_NODE(p)>0) THEN
72 k = k + 4 + cyl_join(n)%NUMBER_PROC + 2*cyl_join(n)%NB_NODE(p) + nspmd
73 ENDIF
74 ENDDO
75 k = k + njoint
76 ! ----------------------
77 ! buffer allocation
78 ALLOCATE(buf_w(k))
79
80 ! write for all processor the number of node per proc
81 DO n=1,njoint
82 buf_w(n) = cyl_join(n)%NB_NODE(p)
83 ENDDO
84 CALL write_i_c(buf_w,njoint)
85 len_ia = len_ia + njoint
86 ! ----------------------
87 ! loop over the CYL_JOINT
88 DO n=1,njoint
89 nb_node_weight(1:nspmd) = 0
90 ! ----------------------
91 ! if 1 or several nodes are on the current processor, write all the stuff
92 IF(cyl_join(n)%NB_NODE(p)>0) THEN
93 ! main processor
94 CALL write_i_c(cyl_join(n)%PROC_MAIN,1)
95 ! number of processor for the current joint
96 CALL write_i_c(cyl_join(n)%NUMBER_PROC,1)
97 ! list of processor for the current joint
98 CALL write_i_c(cyl_join(n)%LIST_PROC,cyl_join(n)%NUMBER_PROC)
99
100 ALLOCATE( secondary_node(cyl_join(n)%NB_NODE(p)) )
101 DO i=1,cyl_join(n)%NB_NODE(p)
102 secondary_node(i) = nodlocal(cyl_join(n)%PROC(p)%NODE(i))
103 ENDDO
104 ! number of node for the current processor and joint
105 CALL write_i_c(secondary_node,cyl_join(n)%NB_NODE(p))
106 ! weight array (0 or 1) for the current processor and joint
107 CALL write_i_c(cyl_join(n)%PROC(p)%WEIGHT,cyl_join(n)%NB_NODE(p))
108 DEALLOCATE( secondary_node )
109 ENDIF
110 ! ----------------------
111 DO i=1,nspmd
112 nb_node_weight(i) = cyl_join(n)%PROC(i)%NB_NODE_WEIGHT
113 ENDDO
114 ! number of node with weight = 1 (all processor) ; use for mpi comm
115 CALL write_i_c(nb_node_weight,nspmd)
116 main_node(1:2) = nodlocal(cyl_join(n)%MAIN_NODE(1:2))
117 ! main nodes (all processor)
118 CALL write_i_c(main_node,2)
119 ENDDO
120
121 is_sms_available = 0
122 IF(joint_sms) is_sms_available = 1
123 CALL write_i_c(is_sms_available,1)
124
125 len_ia = len_ia + k + 1
126 DEALLOCATE(buf_w)
127C
128 RETURN
129 END SUBROUTINE write_joint
logical joint_sms
Definition joint_mod.F:62
type(joint_type), dimension(:), allocatable cyl_join
Definition joint_mod.F:61
subroutine write_joint(ljoint, cep, cel, proc, nodlocal, ljoint_l, len_ia, numnod_l)
Definition write_joint.F:33
void write_i_c(int *w, int *len)