OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
spmd_cell_size_exchange_init.F File Reference
#include "implicit_f.inc"
#include "com01_c.inc"
#include "com04_c.inc"
#include "task_c.inc"
#include "sms_c.inc"
#include "param_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine spmd_cell_size_exchange_init (ircvfrom, isendto, ipari, nin, inter_struct, sort_comm)

Function/Subroutine Documentation

◆ spmd_cell_size_exchange_init()

subroutine spmd_cell_size_exchange_init ( integer, dimension(ninter+1,nspmd+1), intent(in) ircvfrom,
integer, dimension(ninter+1,nspmd+1), intent(in) isendto,
integer, dimension(npari,ninter), intent(in) ipari,
integer, intent(in) nin,
type(inter_struct_type), dimension(ninter), intent(inout) inter_struct,
type(sorting_comm_type), dimension(ninter), intent(inout) sort_comm )

Definition at line 32 of file spmd_cell_size_exchange_init.F.

33!$COMMENT
34! SPMD_CELL_SIZE_EXCHANGE_INIT description :
35! initialization of buffer size + allocation
36! SPMD_CELL_SIZE_EXCHANGE_INIT organization :
37!$ENDCOMMENT
38C-----------------------------------------------
39C M o d u l e s
40C-----------------------------------------------
43 USE tri7box
44C-----------------------------------------------
45C I m p l i c i t T y p e s
46C-----------------------------------------------
47#include "implicit_f.inc"
48C-----------------------------------------------
49C C o m m o n B l o c k s
50C-----------------------------------------------
51#include "com01_c.inc"
52#include "com04_c.inc"
53#include "task_c.inc"
54#include "sms_c.inc"
55#include "param_c.inc"
56C-----------------------------------------------
57C D u m m y A r g u m e n t s
58C-----------------------------------------------
59 INTEGER, INTENT(in) :: NIN
60 INTEGER, DIMENSION(NPARI,NINTER), INTENT(in) :: IPARI
61 INTEGER, DIMENSION(NINTER+1,NSPMD+1), INTENT(in) :: ISENDTO,IRCVFROM
62 TYPE(inter_struct_type), DIMENSION(NINTER), INTENT(inout) :: INTER_STRUCT ! structure for interface
63 TYPE(sorting_comm_type), DIMENSION(NINTER), INTENT(inout) :: SORT_COMM ! structure for interface sorting comm
64C-----------------------------------------------
65C L o c a l V a r i a b l e s
66C-----------------------------------------------
67#ifdef MPI
68 INTEGER :: I,J,NOD,L,L2,KK,IJK,KJI
69 INTEGER :: P,P_LOC
70 INTEGER :: ADRESS,SHIFT_
71 INTEGER :: ISIZ,RSIZ,IDEB,JDEB
72 INTEGER :: NSN,NMN,IGAP,INTTH,INTFRIC,ITYP,ITIED
73 INTEGER :: IFQ,INACTI
74 INTEGER :: LOC_PROC
75! --------------------------------------------------------------------
76
77 loc_proc = ispmd + 1
78 sort_comm(nin)%RSIZ = 0
79 sort_comm(nin)%ISIZ = 0
80
81 igap = ipari(21,nin)
82 intth = ipari(47,nin)
83 intfric = ipari(72,nin)
84 ityp = ipari(7,nin)
85 itied = ipari(85,nin)
86 nmn = ipari(6,nin)
87 nsn = ipari(5,nin)
88 inacti = ipari(22,nin)
89 ifq =ipari(31,nin)
90
91 IF(inacti==5.OR.inacti==6.OR.inacti==7.OR.ifq>0.OR.itied/=0) THEN
92 IF(.NOT.ALLOCATED(inter_struct(nin)%NSNFIOLD) ) THEN
93 ALLOCATE(inter_struct(nin)%NSNFIOLD(nspmd))
94 inter_struct(nin)%NSNFIOLD(1:nspmd) = 0
95 ENDIF
96 DO p = 1, nspmd
97 inter_struct(nin)%NSNFIOLD(p) = nsnfi(nin)%P(p)
98 END DO
99 END IF
100 sort_comm(nin)%NBSEND_NB = 0
101 sort_comm(nin)%NBRECV_NB = 0
102
103 IF(ircvfrom(nin,loc_proc)/=0.OR.isendto(nin,loc_proc)/=0) THEN
104
105 IF(.NOT.ALLOCATED(sort_comm(nin)%REQUEST_NB_R)) THEN
106 ALLOCATE(sort_comm(nin)%REQUEST_NB_R(nspmd) )
107 ENDIF
108 IF(.NOT.ALLOCATED(sort_comm(nin)%REQUEST_NB_S)) THEN
109 ALLOCATE(sort_comm(nin)%REQUEST_NB_S(nspmd) )
110 ENDIF
111 IF(.NOT.ALLOCATED(sort_comm(nin)%NB)) THEN
112 ALLOCATE(sort_comm(nin)%NB(nspmd) )
113 sort_comm(nin)%NB(1:nspmd) = 0
114 ENDIF
115 IF(.NOT.ALLOCATED(sort_comm(nin)%INDEX_RCV)) THEN
116 ALLOCATE( sort_comm(nin)%INDEX_RCV(sort_comm(nin)%PROC_NUMBER) )
117 ENDIF
118
119 rsiz = 8
120 isiz = 6
121
122c specific cases
123c IGAP=1 or IGAP=2
124 IF(igap==1 .OR. igap==2)THEN
125 rsiz = rsiz + 1
126c IGAP=3
127 ELSEIF(igap==3)THEN
128 rsiz = rsiz + 2
129 ENDIF
130
131C thermic
132 IF(intth > 0 ) THEN
133 rsiz = rsiz + 2
134 isiz = isiz + 1
135 ENDIF
136C Friction
137 IF(intfric > 0 ) THEN
138 isiz = isiz + 1
139 ENDIF
140
141C -- IDTMINS==2
142 IF(idtmins == 2)THEN
143 isiz = isiz + 2
144C -- IDTMINS_INT /= 0
145 ELSEIF(idtmins_int/=0)THEN
146 isiz = isiz + 1
147 END IF
148
149 sort_comm(nin)%RSIZ = rsiz
150 sort_comm(nin)%ISIZ = isiz
151
152 IF(isendto(nin,loc_proc)>0) THEN
153 IF(.NOT.ALLOCATED(sort_comm(nin)%SEND_NB)) ALLOCATE(sort_comm(nin)%SEND_NB(nspmd))
154 ENDIF
155 IF(ircvfrom(nin,loc_proc)>0) THEN
156 IF(.NOT.ALLOCATED(sort_comm(nin)%RECV_NB)) ALLOCATE(sort_comm(nin)%RECV_NB(nspmd))
157 ENDIF
158 ENDIF
159#endif
160 RETURN
type(int_pointer), dimension(:), allocatable nsnfi
Definition tri7box.F:440