OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
i2curvv.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!|| i2curvv ../engine/source/interfaces/interf/i2curvv.F
25!||--- called by ------------------------------------------------------
26!|| intti2v ../engine/source/interfaces/interf/intti2v.F
27!||--- calls -----------------------------------------------------
28!|| i2_fform ../engine/source/interfaces/interf/i2_fform.F
29!|| i2curv_rep ../engine/source/interfaces/interf/i2curv_rep.F
30!|| inv3 ../engine/source/elements/joint/rskew33.F
31!||====================================================================
32 SUBROUTINE i2curvv(
33 . NSN ,NMN ,MS ,V ,A ,
34 . AR ,VR ,X ,IRECT ,NSV ,
35 . MSR ,IRTL ,CRST ,WEIGHT )
36C-----------------------------------------------
37C I m p l i c i t T y p e s
38C-----------------------------------------------
39#include "implicit_f.inc"
40C-----------------------------------------------
41C D u m m y A r g u m e n t s
42C-----------------------------------------------
43 INTEGER NSN,NMN,
44 . IRECT(4,*), MSR(*), NSV(*), IRTL(*),WEIGHT(*)
45C REAL
47 . a(3,*),v(3,*),ar(3,*),vr(3,*),x(3,*),ms(*),crst(2,*)
48C-----------------------------------------------
49C L o c a l V a r i a b l e s
50C-----------------------------------------------
51 INTEGER NIR,I,J,L,II,JJ,IS
52 INTEGER INOD(4)
53C REAL
55 . ls1,ls2,lt1,lt2,ls,lt,s,t
57 . vs(6),as(6),vm(6,4),am(6,4),rot(9),roti(9),
58 . h(4),hh(4),hrs(4),hrt(4),hps(4),hpt(4),hprs(4),hprt(4),
59 . hxs(4),hxt(4)
60C=======================================================================
61 DO ii=1,nsn
62 is=nsv(ii)
63 IF (is > 0) THEN
64 l=irtl(ii)
65 nir = 4
66 DO jj=1,nir
67 inod(jj) = irect(jj,l)
68 ENDDO
69C---
70 CALL i2curv_rep(inod , x ,v ,ls1 ,ls2 ,
71 . lt1 ,lt2 ,rot(1) ,rot(4) ,rot(7) ,
72 . rot(2) ,rot(5) ,rot(8) ,rot(3) ,rot(6) ,
73 . rot(9) )
74 CALL inv3(rot,roti)
75C---
76 s=crst(1,ii)
77 t=crst(2,ii)
78 CALL i2_fform(
79 . nir,s,t,h,hh,hrs,hrt,hps,hpt,hprs,hprt,
80 . hxs,hxt,ls1,ls2,lt1,lt2,ls,lt)
81C---
82 DO jj=1,nir
83 j=inod(jj)
84 vm(1,jj) = rot(1)*v(1,j) + rot(4)*v(2,j) + rot(7)*v(3,j)
85 vm(2,jj) = rot(2)*v(1,j) + rot(5)*v(2,j) + rot(8)*v(3,j)
86 vm(3,jj) = rot(3)*v(1,j) + rot(6)*v(2,j) + rot(9)*v(3,j)
87 am(1,jj) = rot(1)*a(1,j) + rot(4)*a(2,j) + rot(7)*a(3,j)
88 am(2,jj) = rot(2)*a(1,j) + rot(5)*a(2,j) + rot(8)*a(3,j)
89 am(3,jj) = rot(3)*a(1,j) + rot(6)*a(2,j) + rot(9)*a(3,j)
90 vm(4,jj) = rot(1)*vr(1,j)+rot(4)*vr(2,j)+rot(7)*vr(3,j)
91 vm(5,jj) = rot(2)*vr(1,j)+rot(5)*vr(2,j)+rot(8)*vr(3,j)
92 vm(6,jj) = rot(3)*vr(1,j)+rot(6)*vr(2,j)+rot(9)*vr(3,j)
93 am(4,jj) = rot(1)*ar(1,j)+rot(4)*ar(2,j)+rot(7)*ar(3,j)
94 am(5,jj) = rot(2)*ar(1,j)+rot(5)*ar(2,j)+rot(8)*ar(3,j)
95 am(6,jj) = rot(3)*ar(1,j)+rot(6)*ar(2,j)+rot(9)*ar(3,j)
96 ENDDO
97C---
98 vs = zero
99 as = zero
100 DO jj=1,nir
101 vs(1) = vs(1) + h(jj) * vm(1,jj)
102 vs(2) = vs(2) + h(jj) * vm(2,jj)
103 vs(3) = vs(3) + hh(jj) *vm(3,jj)
104 . + hrs(jj)*vm(4,jj) + hrt(jj) *vm(5,jj)
105 vs(4) = vs(4) + hps(jj)*vm(3,jj) + hprs(jj)*vm(4,jj)
106 . + hxs(jj) *vm(5,jj)
107 vs(5) = vs(5) + hpt(jj)*vm(3,jj) + hprt(jj)*vm(5,jj)
108 . + hxt(jj) *vm(4,jj)
109 vs(6) = vs(6) + h(jj) * vm(6,jj)
110C
111 as(1) = as(1) + h(jj) * am(1,jj)
112 as(2) = as(2) + h(jj) * am(2,jj)
113 as(3) = as(3) + hh(jj) *am(3,jj)
114 . + hrs(jj)*am(4,jj)
115 . + hrt(jj)*am(5,jj)
116 as(4) = as(4) + hps(jj)*am(3,jj) + hprs(jj)*am(4,jj)
117 . + hxs(jj) *am(5,jj)
118 as(5) = as(5) + hpt(jj)*am(3,jj) + hprt(jj)*am(5,jj)
119 . + hxt(jj) *am(4,jj)
120 as(6) = as(6) + h(jj) * am(6,jj)
121 ENDDO
122C---
123 a(1,is) = roti(1)*as(1)+roti(4)*as(2)+roti(7)*as(3)
124 a(2,is) = roti(2)*as(1)+roti(5)*as(2)+roti(8)*as(3)
125 a(3,is) = roti(3)*as(1)+roti(6)*as(2)+roti(9)*as(3)
126 v(1,is) = roti(1)*vs(1)+roti(4)*vs(2)+roti(7)*vs(3)
127 v(2,is) = roti(2)*vs(1)+roti(5)*vs(2)+roti(8)*vs(3)
128 v(3,is) = roti(3)*vs(1)+roti(6)*vs(2)+roti(9)*vs(3)
129 ar(1,is)=roti(1)*as(4)+roti(4)*as(5)+roti(7)*as(6)
130 ar(2,is)=roti(2)*as(4)+roti(5)*as(5)+roti(8)*as(6)
131 ar(3,is)=roti(3)*as(4)+roti(6)*as(5)+roti(9)*as(6)
132 vr(1,is)=roti(1)*vs(4)+roti(4)*vs(5)+roti(7)*vs(6)
133 vr(2,is)=roti(2)*vs(4)+roti(5)*vs(5)+roti(8)*vs(6)
134 vr(3,is)=roti(3)*vs(4)+roti(6)*vs(5)+roti(9)*vs(6)
135C
136 ENDIF
137 ENDDO
138C-----------
139 RETURN
140 END
#define my_real
Definition cppsort.cpp:32
subroutine i2_fform(nir, s, t, h, hh, hrs, hrt, hps, hpt, hprs, hprt, hxs, hxt, ls1, ls2, lt1, lt2, ls, lt)
Definition i2_fform.F:33
subroutine i2curv_rep(inod, x, v, ls1, ls2, lt1, lt2, e1x, e1y, e1z, e2x, e2y, e2z, e3x, e3y, e3z)
Definition i2curv_rep.F:35
subroutine i2curvv(nsn, nmn, ms, v, a, ar, vr, x, irect, nsv, msr, irtl, crst, weight)
Definition i2curvv.F:36
subroutine inv3(a, b)
Definition inv3.F:29