OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
i1tid2.F File Reference
#include "implicit_f.inc"
#include "units_c.inc"
#include "scr03_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine i1tid2 (x, irect, crst, msr, nsv, iloc, irtl, nsn, itab, id, titr, numnod)

Function/Subroutine Documentation

◆ i1tid2()

subroutine i1tid2 ( x,
integer, dimension(4,*) irect,
crst,
integer, dimension(*) msr,
integer, dimension(*) nsv,
integer, dimension(*) iloc,
integer, dimension(*) irtl,
integer nsn,
integer, dimension(numnod) itab,
integer id,
character(len=nchartitle) titr,
integer, intent(in) numnod )

Definition at line 34 of file i1tid2.F.

35C-----------------------------------------------
36C M o d u l e s
37C-----------------------------------------------
38 USE message_mod
40 USE format_mod , ONLY : fmw_5i_f
41C-----------------------------------------------
42C I m p l i c i t T y p e s
43C-----------------------------------------------
44#include "implicit_f.inc"
45C-----------------------------------------------
46C C o m m o n B l o c k s
47C-----------------------------------------------
48#include "units_c.inc"
49#include "scr03_c.inc"
50C-----------------------------------------------
51C D u m m y A r g u m e n t s
52C-----------------------------------------------
53 INTEGER,INTENT(IN) :: NUMNOD
54 INTEGER NSN
55 INTEGER IRECT(4,*), MSR(*), NSV(*), ILOC(*), IRTL(*), ITAB(NUMNOD)
56 my_real x(3,numnod), crst(2,*)
57 INTEGER ID
58 CHARACTER(LEN=NCHARTITLE) :: TITR
59C-----------------------------------------------
60C L o c a l V a r i a b l e s
61C-----------------------------------------------
62 INTEGER IER1, II, I, J, K, L, M, JJ, IER2
63 my_real n2, n3, ys, zs, t2, t3, xl, ss,ym1,ym2,zm1,zm2
64C-----------------------------------------------
65C S o u r c e L i n e s
66C-----------------------------------------------
67 ier1=0
68 DO ii=1,nsn
69 i=nsv(ii)
70 j=iloc(ii) ! nearest lag node (main) from secnd node (ale)
71 k=msr(j)
72 l=irtl(ii)
73 m=msr(irect(1,l))
74 ym1=x(2,m)
75 zm1=x(3,m)
76 m=msr(irect(2,l))
77 ym2=x(2,m)
78 zm2=x(3,m)
79 ys =x(2,i)
80 zs =x(3,i)
81 t2=ym2-ym1
82 t3=zm2-zm1
83 xl=sqrt(t2**2+t3**2)
84 IF(xl == zero)THEN
85 CALL ancmsg(msgid=80,msgtype=msgerror,anmode=aninfo,i1=id,c1=titr,i2=l,i3=itab(msr(irect(1,l))),i4=itab(msr(irect(2,l))))
86 ENDIF
87 t2=t2/xl
88 t3=t3/xl
89 n2= t3
90 n3=-t2
91 ss=t2*(ys-ym1)+t3*(zs-zm1)
92 ss=ss/xl
93 ss=two*ss-one
94 crst(1,ii)=ss
95 crst(2,ii)=-one
96 ier2=0
97 IF(ss> onep05 .OR. ss<-onep05)THEN
98 ier1=ier1+1
99 ier2=1
100 ENDIF
101 IF(ipri>=1 .OR. ier2>0)THEN
102 WRITE(iout,fmt=fmw_5i_f)itab(i), itab(k), l, itab(msr(irect(1,l))), itab(msr(irect(2,l))), ss
103 ENDIF
104 ENDDO !next II
105
106 IF(ier1 > 0)THEN
107 ! ** ERROR TIED INTERFACE: SECND NODE OUTSIDE main SEGMENT
108 CALL ancmsg(msgid=81,msgtype=msgerror,anmode=aninfo,i1=id,c1=titr)
109 ENDIF
110C-----------------------------------------------
111 RETURN
112
#define my_real
Definition cppsort.cpp:32
initmumps id
integer, parameter nchartitle
subroutine ancmsg(msgid, msgtype, anmode, i1, i2, i3, i4, i5, i6, i7, i8, i9, i10, i11, i12, i13, i14, i15, i16, i17, i18, i19, i20, r1, r2, r3, r4, r5, r6, r7, r8, r9, c1, c2, c3, c4, c5, c6, c7, c8, c9, prmode)
Definition message.F:889