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

Go to the source code of this file.

Functions/Subroutines

subroutine i3msr3 (x, irect, lmsr, msr, nsv, iloc, irtl, nseg, xface, lft, llt, nft)

Function/Subroutine Documentation

◆ i3msr3()

subroutine i3msr3 ( dimension(3,*), intent(in) x,
integer, dimension(4,*), intent(in) irect,
integer, dimension(*), intent(in) lmsr,
integer, dimension(*), intent(in) msr,
integer, dimension(*), intent(in) nsv,
integer, dimension(*), intent(in) iloc,
integer, dimension(*), intent(inout) irtl,
integer, dimension(*), intent(in) nseg,
intent(in) xface,
integer, intent(inout) lft,
integer, intent(inout) llt,
integer, intent(inout) nft )

Definition at line 32 of file i3msr3.F.

36C-----------------------------------------------
37C I m p l i c i t T y p e s
38C-----------------------------------------------
39#include "implicit_f.inc"
40C-----------------------------------------------
41C G l o b a l P a r a m e t e r s
42C-----------------------------------------------
43#include "mvsiz_p.inc"
44C-----------------------------------------------
45C D u m m y A r g u m e n t s
46C-----------------------------------------------
47 INTEGER, INTENT(INOUT) :: LFT
48 INTEGER, INTENT(INOUT) :: LLT
49 INTEGER, INTENT(INOUT) :: NFT
50 INTEGER, INTENT(IN) :: IRECT(4,*), LMSR(*), MSR(*), NSV(*), ILOC(*), NSEG(*)
51 INTEGER, INTENT(INOUT) :: IRTL(*)
52 my_real, DIMENSION(MVSIZ), INTENT(IN) :: xface
53 my_real, INTENT(IN) :: x(3,*)
54C-----------------------------------------------
55C C o m m o n B l o c k s
56C-----------------------------------------------
57C-----------------------------------------------
58C L o c a l V a r i a b l e s
59C-----------------------------------------------
60 INTEGER I, IL, JL, L, JJJ, JJ, J1, J2, LL1, LL2, LL, LG, IG, JG, M, N
61 INTEGER KM1(4), KN1(4), LSEG, LSEG_NEW
62 my_real bmin, bmax
63 DATA km1/2,3,4,1/
64 DATA kn1/4,1,2,3/
65C-----------------------------------------------
66 DO i=lft,llt
67 il=i+nft
68 ig=nsv(il)
69 jl=iloc(il)
70 jg=msr(jl)
71 l=irtl(il)
72 IF(xface(i)==zero)THEN
73 irtl(il)=max(l,1)
74 ELSE
75 bmax=-ep30
76 lseg_new=0
77C
78 IF(l==0) GOTO 100
79 lseg=l
80 DO jjj=1,4
81 jj=jjj
82 IF(irect(jj,l)==jl) EXIT
83 ENDDO
84 j1=km1(jj)
85 j2=kn1(jj)
86 IF(jj==3.AND.irect(3,l)==irect(4,l)) j1=1
87 m=msr(irect(j1,l))
88 n=msr(irect(j2,l))
89 CALL nearest_seg(x, ig, jg, m, n, lseg, lseg_new, bmin, bmax)
90 IF(bmin >= zero) GO TO 200
91C
92 100 CONTINUE
93 ll1=nseg(jl)
94 ll2=nseg(jl+1)-1
95 DO ll=ll1,ll2
96 lg=lmsr(ll)
97 lseg=lg
98 IF(l==lg) cycle
99 DO jjj=1,4
100 jj=jjj
101 IF(irect(jj,lg)==jl) EXIT
102 ENDDO
103 j1=km1(jj)
104 j2=kn1(jj)
105 IF(jj==3.AND.irect(3,lg)==irect(4,lg)) j1=1
106 m=msr(irect(j1,lg))
107 n=msr(irect(j2,lg))
108 CALL nearest_seg(x, ig, jg, m, n, lseg, lseg_new, bmin, bmax)
109 IF(bmin < zero) cycle
110 irtl(il)=lseg_new
111 GO TO 200
112 ENDDO !LL=LL1,LL2
113C
114 irtl(il)=lseg_new
115 200 CONTINUE
116 ENDIF
117 ENDDO !I=LFT,LLT
118C
119 RETURN
#define my_real
Definition cppsort.cpp:32
#define max(a, b)
Definition macros.h:21
subroutine nearest_seg(x, is, m1, m2, m3, lseg, lseg_new, bmin, bmax)
Definition nearest_seg.F:30