OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
i3msr3.F
Go to the documentation of this file.
1Copyright> OpenRadioss
2Copyright> Copyright (C) 1986-2025 Altair Engineering Inc.
3Copyright>
4Copyright> This program is free software: you can redistribute it and/or modify
5Copyright> it under the terms of the GNU Affero General Public License as published by
6Copyright> the Free Software Foundation, either version 3 of the License, or
7Copyright> (at your option) any later version.
8Copyright>
9Copyright> This program is distributed in the hope that it will be useful,
10Copyright> but WITHOUT ANY WARRANTY; without even the implied warranty of
11Copyright> MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12Copyright> GNU Affero General Public License for more details.
13Copyright>
14Copyright> You should have received a copy of the GNU Affero General Public License
15Copyright> along with this program. If not, see <https://www.gnu.org/licenses/>.
16Copyright>
17Copyright>
18Copyright> Commercial Alternative: Altair Radioss Software
19Copyright>
20Copyright> As an alternative to this open-source version, Altair also offers Altair Radioss
21Copyright> software under a commercial license. Contact Altair to discuss further if the
22Copyright> commercial version may interest you: https://www.altair.com/radioss/.
23!||====================================================================
24!|| i3msr3 ../engine/source/interfaces/inter3d/i3msr3.F
25!||--- called by ------------------------------------------------------
26!|| i6main ../engine/source/interfaces/inter3d/i6main.F
27!|| i9main3 ../engine/source/interfaces/int09/i9main3.F
28!|| intvo3 ../engine/source/interfaces/inter3d/intvo3.F
29!||--- calls -----------------------------------------------------
30!|| nearest_seg ../common_source/interf/nearest_seg.F
31!||====================================================================
32 SUBROUTINE i3msr3(
33 1 X, IRECT, LMSR, MSR,
34 2 NSV, ILOC, IRTL, NSEG,
35 3 XFACE, LFT, LLT, NFT)
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
120 END
#define my_real
Definition cppsort.cpp:32
subroutine i3msr3(x, irect, lmsr, msr, nsv, iloc, irtl, nseg, xface, lft, llt, nft)
Definition i3msr3.F:36
#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