OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
spmd_collect_seatbelt.F File Reference
#include "implicit_f.inc"
#include "spmd.inc"
#include "com01_c.inc"
#include "task_c.inc"
#include "param_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine spmd_collect_seatbelt ()

Function/Subroutine Documentation

◆ spmd_collect_seatbelt()

subroutine spmd_collect_seatbelt

Definition at line 33 of file spmd_collect_seatbelt.F.

34C-----------------------------------------------
35 USE seatbelt_mod
36C-----------------------------------------------
37C I m p l i c i t T y p e s
38C-----------------------------------------------
39 USE spmd_comm_world_mod, ONLY : spmd_comm_world
40#include "implicit_f.inc"
41C-----------------------------------------------------------------
42C M e s s a g e P a s s i n g
43C-----------------------------------------------
44#include "spmd.inc"
45C-----------------------------------------------
46C C o m m o n B l o c k s
47C-----------------------------------------------
48#include "com01_c.inc"
49#include "task_c.inc"
50#include "param_c.inc"
51C-----------------------------------------------
52C L o c a l V a r i a b l e s
53C-----------------------------------------------
54#ifdef MPI
55 INTEGER MSGTYP,MSGOFF,IERROR,LOC_PROC,NN,L,I,K,M,N,II,J,
56 . IDEB,SIZ,A_AR,NBIRECV,INDEX,
57 . IRINDEX(NSPMD),REQ_R(NSPMD),IAD_RECV(NSPMD),
58 . STATUS(MPI_STATUS_SIZE)
60 . sbuf(7*nslipring+4*nretractor),rbuf(7*nslipring_g+4*nretractor_g),fac
61 DATA msgoff/203/
62C-----------------------------------------------
63C S o u r c e L i n e s
64C-----------------------------------------------
65 loc_proc = ispmd + 1
66C
67 IF (loc_proc==1) THEN
68 ideb = 1
69C
70 DO ii = 1, nseatbelt_th_proc
71 i = seatbelt_th_exch(ii)%ID_PROC
72 iad_recv(i) = ideb
73 irindex(ii) = i
74 siz = 7*seatbelt_th_exch(ii)%NSLIPRING + 4*seatbelt_th_exch(ii)%NRETRACTOR
75 msgtyp = msgoff
76 CALL mpi_irecv(
77 s rbuf(ideb),siz,real,it_spmd(i),msgtyp,
78 g spmd_comm_world,req_r(ii),ierror)
79 ideb = ideb + siz
80 END DO
81C
82 DO ii = 1, nseatbelt_th_proc
83 CALL mpi_waitany(nseatbelt_th_proc,req_r,index,status,ierror)
84 i = irindex(index)
85 l = iad_recv(i)
86C
87 DO n = 1,seatbelt_th_exch(index)%NSLIPRING
88 k = nint(rbuf(l))
89 DO m=1,6
90 th_slipring(k,m) = rbuf(l+m)
91 ENDDO
92 l = l + 7
93 END DO
94C
95 DO n = 1,seatbelt_th_exch(index)%NRETRACTOR
96 k = nint(rbuf(l))
97 DO m=1,3
98 th_retractor(k,m) = rbuf(l+m)
99 ENDDO
100 l = l + 4
101 END DO
102 END DO
103C
104 ELSE
105C
106 k = 0
107 sbuf = 0
108C
109 DO n = 1, nslipring
110 sbuf(k+1) = slipring(n)%IDG
111 k = k + 1
112 fac = one/slipring(n)%NFRAM
113 DO l = 1,slipring(n)%NFRAM
114C-- IF NFRAM > 1 - RINGLSIP and BETA are average of the 1d sliprings - FORCE is the sum - GAMMA = ZERO
115 sbuf(k+1) = sbuf(k+1) + fac*slipring(n)%FRAM(l)%RINGSLIP
116 sbuf(k+2) = sbuf(k+2) + slipring(n)%FRAM(l)%SLIP_FORCE(3)
117 sbuf(k+3) = sbuf(k+3) + slipring(n)%FRAM(l)%SLIP_FORCE(1)
118 sbuf(k+4) = sbuf(k+4) + slipring(n)%FRAM(l)%SLIP_FORCE(2)
119 sbuf(k+5) = sbuf(k+5) + fac*slipring(n)%FRAM(l)%BETA
120 sbuf(k+6) = sbuf(k+6) + fac*slipring(n)%FRAM(l)%ORIENTATION_ANGLE
121 END DO
122 k = k + 6
123 END DO
124C
125 DO n = 1, nretractor
126 sbuf(k+1) = retractor(n)%IDG
127 sbuf(k+2) = retractor(n)%RINGSLIP
128 sbuf(k+3) = retractor(n)%RET_FORCE
129 sbuf(k+4) = retractor(n)%LOCKED
130 k = k + 4
131 END DO
132C
133 siz = k
134 IF (siz > 0) THEN
135 msgtyp=msgoff
136 CALL mpi_send(sbuf,siz,real,it_spmd(1),msgtyp,
137 g spmd_comm_world,ierror)
138 ENDIF
139C
140 END IF
141C
142#endif
143 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine mpi_send(buf, cnt, datatype, dest, tag, comm, ierr)
Definition mpi.f:480
subroutine mpi_waitany(cnt, array_of_requests, index, status, ierr)
Definition mpi.f:549
subroutine mpi_irecv(buf, cnt, datatype, source, tag, comm, ireq, ierr)
Definition mpi.f:372
integer nseatbelt_th_proc
type(retractor_struct), dimension(:), allocatable retractor
type(seatbelt_th_exch_struct), dimension(:), allocatable seatbelt_th_exch
type(slipring_struct), dimension(:), allocatable slipring