OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
m14ama.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!|| m14ama ../engine/source/materials/mat/mat014/m14ama.F
25!||--- called by ------------------------------------------------------
26!|| m12law ../engine/source/materials/mat/mat012/m12law.F
27!|| m14law ../engine/source/materials/mat/mat014/m14law.F
28!||====================================================================
29 SUBROUTINE m14ama(
30 1 PM, A, RX, RY,
31 2 RZ, SX, SY, SZ,
32 3 AX, AY, AZ, BX,
33 4 BY, BZ, CX, CY,
34 5 CZ, NEL, JCVT, JSPH)
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 C o m m o n B l o c k s
45C-----------------------------------------------
46#include "com01_c.inc"
47#include "param_c.inc"
48C-----------------------------------------------
49C D u m m y A r g u m e n t s
50C-----------------------------------------------
51 INTEGER, INTENT(IN) :: NEL
52 INTEGER, INTENT(IN) :: JCVT
53 INTEGER, INTENT(IN) :: JSPH
54C REAL
55 my_real PM(NPROPM,*), A(MVSIZ,6)
56 my_real
57 . rx(*), ry(*), rz(*), sx(*), sy(*), sz(*),
58 . ax(*), ay(*), az(*), bx(*), by(*), bz(*), cx(*), cy(*),cz(*)
59C-----------------------------------------------
60C L o c a l V a r i a b l e s
61C-----------------------------------------------
62 INTEGER I
63C REAL
64 my_real
65 . TX(MVSIZ), TY(MVSIZ),TZ(MVSIZ), RR
66C-----------------------------------------------
67C
68 IF (jsph==1) THEN
69 DO i=1,nel
70 ax(i)=a(i,1)
71 ay(i)=a(i,2)
72 az(i)=a(i,3)
73 bx(i)=a(i,4)
74 by(i)=a(i,5)
75 bz(i)=a(i,6)
76 cx(i)=ay(i)*bz(i)-az(i)*by(i)
77 cy(i)=az(i)*bx(i)-ax(i)*bz(i)
78 cz(i)=ax(i)*by(i)-ay(i)*bx(i)
79 END DO
80C
81 ELSEIF(jcvt==0)THEN
82 IF (n2d==0) THEN
83 DO i=1,nel
84 rr=one/sqrt(rx(i)**2+ry(i)**2+rz(i)**2)
85 rx(i)=rx(i)*rr
86 ry(i)=ry(i)*rr
87 rz(i)=rz(i)*rr
88C
89 tx(i)=ry(i)*sz(i)-rz(i)*sy(i)
90 ty(i)=rz(i)*sx(i)-rx(i)*sz(i)
91 tz(i)=rx(i)*sy(i)-ry(i)*sx(i)
92 rr=one/sqrt(tx(i)**2+ty(i)**2+tz(i)**2)
93 tx(i)=tx(i)*rr
94 ty(i)=ty(i)*rr
95 tz(i)=tz(i)*rr
96C
97 sx(i)=ty(i)*rz(i)-tz(i)*ry(i)
98 sy(i)=tz(i)*rx(i)-tx(i)*rz(i)
99 sz(i)=tx(i)*ry(i)-ty(i)*rx(i)
100 rr=1./sqrt(sx(i)**2+sy(i)**2+sz(i)**2)
101 sx(i)=sx(i)*rr
102 sy(i)=sy(i)*rr
103 sz(i)=sz(i)*rr
104 ENDDO
105 ELSE
106 DO i=1,nel
107 rr=one/sqrt(sy(i)**2+sz(i)**2)
108 sy(i)=sy(i)*rr
109 sz(i)=sz(i)*rr
110C
111 ty(i)=-rx(i)*sz(i)
112 tz(i)=rx(i)*sy(i)
113 rr=one/sqrt(ty(i)**2+tz(i)**2)
114 ty(i)=ty(i)*rr
115 tz(i)=tz(i)*rr
116 ENDDO
117 ENDIF
118C
119 DO 200 i=1,nel
120 ax(i)= a(i,1)*rx(i)+a(i,2)*sx(i)+a(i,3)*tx(i)
121 ay(i)= a(i,1)*ry(i)+a(i,2)*sy(i)+a(i,3)*ty(i)
122 az(i)= a(i,1)*rz(i)+a(i,2)*sz(i)+a(i,3)*tz(i)
123C
124 bx(i)= a(i,4)*rx(i)+a(i,5)*sx(i)+a(i,6)*tx(i)
125 by(i)= a(i,4)*ry(i)+a(i,5)*sy(i)+a(i,6)*ty(i)
126 bz(i)= a(i,4)*rz(i)+a(i,5)*sz(i)+a(i,6)*tz(i)
127C
128C 22/06/98
129C CX(I)= A(7,I)*RX(I)+A(8,I)*SX(I)+A(9,I)*TX(I)
130C CY(I)= A(7,I)*RY(I)+A(8,I)*SY(I)+A(9,I)*TY(I)
131C CZ(I)= A(7,I)*RZ(I)+A(8,I)*SZ(I)+A(9,I)*TZ(I)
132C
133 cx(i)=ay(i)*bz(i)-az(i)*by(i)
134 cy(i)=az(i)*bx(i)-ax(i)*bz(i)
135 cz(i)=ax(i)*by(i)-ay(i)*bx(i)
136 200 CONTINUE
137C-------------------------------
138C CO-ROTATIONAL FORMULATION IN ORTHOTROPIC CO-ROTATIONAL SYSTEM.
139 ELSE
140 DO 500 i=1,nel
141 ax(i)=one
142 bx(i)=zero
143 cx(i)=zero
144 ay(i)=zero
145 by(i)=one
146 cy(i)=zero
147 az(i)=zero
148 bz(i)=zero
149 cz(i)=one
150 500 CONTINUE
151 ENDIF
152C
153 RETURN
154 END
subroutine m14ama(pm, a, rx, ry, rz, sx, sy, sz, ax, ay, az, bx, by, bz, cx, cy, cz, nel, jcvt, jsph)
Definition m14ama.F:35