OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
line_decomp.F File Reference
#include "implicit_f.inc"
#include "com04_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine line_decomp (igrslin)

Function/Subroutine Documentation

◆ line_decomp()

subroutine line_decomp ( type (surf_), dimension(nslin) igrslin)

Definition at line 32 of file line_decomp.F.

33C-----------------------------------------------
34C M o d u l e s
35C-----------------------------------------------
36 USE front_mod
37 USE groupdef_mod
38C-----------------------------------------------
39C I m p l i c i t T y p e s
40C-----------------------------------------------
41#include "implicit_f.inc"
42C-----------------------------------------------
43C C o m m o n B l o c k s
44C-----------------------------------------------
45#include "com04_c.inc"
46C-----------------------------------------------
47C D u m m y A r g u m e n t s
48C-----------------------------------------------
49 TYPE (SURF_) , DIMENSION(NSLIN) :: IGRSLIN
50C-----------------------------------------------
51C L o c a l V a r i a b l e s
52C-----------------------------------------------
53 INTEGER NN,IAD,IAD1,IAD2,IAD11,ND1,ND2,P,P1,P2
54 INTEGER I,J
55 LOGICAL PSEARCH
56C---------------------------------------------------------------
57C Care : In lines - Element ID is wrong after Element grouping
58C I reuse last field to store the processor ID.
59C When lines are taken care in Element Grouping
60C 1. Set processor only when no element is set in lines
61C 2. Split lines accordingly
62! /LINE are not used in the engine and the split is wrong in
63! case of useless line (ie. when a line is defined but not
64! used by an interface or other stuffs) -->
65! 2 nodes (defining a segment) can be on 2 different processors
66! in this case, the segment is not written in the restart file
67! one could also define the nodes on the same processor but
68! it will increase the comm.
69C---------------------------------------------------------------
70 DO i = 1, nslin
71 nn = igrslin(i)%NSEG
72 DO j = 1, nn
73 p=0
74 psearch= .true.
75 nd1 = igrslin(i)%NODES(j,1)
76 nd2 = igrslin(i)%NODES(j,2)
77C For better performance, I don't use nlocal, but use low level system
78 iad1 = ifront%IENTRY(nd1)
79 iad2 = ifront%IENTRY(nd2)
80
81 iad11 = iad1
82C
83C Initialization
84C
85 p1 = ifront%P(1,iad1)
86 p2 = ifront%P(1,iad2)
87C
88C Common case : node are on same domain
89C
90 IF(p1==p2) THEN
91 p=p1
92 psearch= .false.
93 ENDIF
94C
95 DO WHILE (psearch)
96
97C P1 equal to p2 found
98 IF(p1 == p2) THEN
99 p=p1
100 psearch= .false.
101 ENDIF
102
103C Search leaves - in case 2 nodes from segments are in different domain.
104 IF(p1 == 0)THEN
105 print*,'ERROR P1',nd1,nd2
106 CALL my_exit(2)
107 ENDIF
108 IF(p2 == 0)THEN
109 print*,'ERROR P2',nd1,nd2
110 CALL my_exit(2)
111 ENDIF
112C Move forward
113
114 ! ---------------------
115 IF(p1 < p2)THEN
116 iad1 = ifront%P(2,iad1)
117 ENDIF
118
119 IF(p1 > p2)THEN
120 iad2 = ifront%P(2,iad2)
121 ENDIF
122 ! ---------------------
123 ! iad1 = 0 or iad2 = 0 --> the last processor id
124 ! is reached
125 IF(iad1==0.OR.iad2==0) THEN
126 ! skip this segment
127 p1=0
128 p2=0
129 p=0
130 psearch= .false.
131 ELSE
132 p1 = ifront%P(1,iad1)
133 p2 = ifront%P(1,iad2)
134 ENDIF
135 ! ---------------------
136 ENDDO ! DO WHILE (PSEARCH)
137C For this split - I use 3rd field to set Processor (supposed empty)
138
139 igrslin(i)%PROC(j) = p
140
141 ENDDO ! DO J = 1, NN
142 ENDDO ! DO I = 1, NSLIN
143
144 RETURN
void my_exit(int *i)
Definition analyse.c:1038
type(my_front) ifront
Definition front_mod.F:93