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

Go to the source code of this file.

Functions/Subroutines

subroutine i3loc3 (x, irect, lmsr, msr, nsv, iloc, nseg, xi, yi, zi, xface, lft, llt, nft)

Function/Subroutine Documentation

◆ i3loc3()

subroutine i3loc3 ( x,
integer, dimension(4,*) irect,
integer, dimension(*) lmsr,
integer, dimension(*) msr,
integer, dimension(*) nsv,
integer, dimension(*) iloc,
integer, dimension(*) nseg,
intent(inout) xi,
intent(inout) yi,
intent(inout) zi,
intent(inout) xface,
integer, intent(inout) lft,
integer, intent(inout) llt,
integer, intent(inout) nft )

Definition at line 30 of file i3loc3.F.

35C-----------------------------------------------
36C I m p l i c i t T y p e s
37C-----------------------------------------------
38#include "implicit_f.inc"
39C-----------------------------------------------
40C G l o b a l P a r a m e t e r s
41C-----------------------------------------------
42#include "mvsiz_p.inc"
43C-----------------------------------------------
44C D u m m y A r g u m e n t s
45C-----------------------------------------------
46 INTEGER, INTENT(INOUT) :: LFT
47 INTEGER, INTENT(INOUT) :: LLT
48 INTEGER, INTENT(INOUT) :: NFT
49 INTEGER IRECT(4,*), LMSR(*), MSR(*), NSV(*), ILOC(*), NSEG(*)
50C REAL
52 . x(3,*)
53C-----------------------------------------------
54C C o m m o n B l o c k s
55C-----------------------------------------------
56 my_real, DIMENSION(MVSIZ), INTENT(INOUT) :: xi,yi,zi,xface
57C-----------------------------------------------
58C L o c a l V a r i a b l e s
59C-----------------------------------------------
60 INTEGER I, IL, IG, JL, JLNEW, LL2, LL1, LL, LG, J, K, M, N, JG,
61 . KG, MG, NG
62C REAL
64 . gms, cms,
65 . dms, ems, fms
66C-----------------------------------------------
67
68 DO 100 i=lft,llt
69 xface(i)=one
70 il=i+nft
71 ig=nsv(il)
72 xi(i)=x(1,ig)
73 yi(i)=x(2,ig)
74 zi(i)=x(3,ig)
75 100 CONTINUE
76C
77 DO 130 i=lft,llt
78 il=i+nft
79 ig=nsv(il)
80 jl=iloc(il)
81 jlnew=jl
82 ll2=nseg(jl+1)-1
83 ll1=nseg(jl)
84 gms=1.e30
85 DO 120 ll=ll1,ll2
86 lg=lmsr(ll)
87 j=irect(1,lg)
88 k=irect(2,lg)
89 m=irect(3,lg)
90 n=irect(4,lg)
91 jg=msr(j)
92 kg=msr(k)
93 mg=msr(m)
94 ng=msr(n)
95 cms=(xi(i)-x(1,jg))**2+(yi(i)-x(2,jg))**2+(zi(i)-x(3,jg))**2
96 dms=(xi(i)-x(1,kg))**2+(yi(i)-x(2,kg))**2+(zi(i)-x(3,kg))**2
97 ems=(xi(i)-x(1,mg))**2+(yi(i)-x(2,mg))**2+(zi(i)-x(3,mg))**2
98 fms=(xi(i)-x(1,ng))**2+(yi(i)-x(2,ng))**2+(zi(i)-x(3,ng))**2
99 IF(cms<gms) THEN
100 gms=cms
101 jlnew=j
102 ENDIF
103 IF(dms<gms) THEN
104 gms=dms
105 jlnew=k
106 ENDIF
107 IF(ems<gms) THEN
108 gms=ems
109 jlnew=m
110 ENDIF
111 IF(fms<gms) THEN
112 gms=fms
113 jlnew=n
114 ENDIF
115 120 CONTINUE
116 iloc(il)=jlnew
117 130 CONTINUE
118C
119 RETURN
#define my_real
Definition cppsort.cpp:32