OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
spreploc.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!|| spreploc ../engine/source/elements/sph/spreploc.f
25!||--- called by ------------------------------------------------------
26!|| spstres ../engine/source/elements/sph/spstres.F
27!||====================================================================
28 SUBROUTINE spreploc(
29 1 REPLOC, WXX, WYY, WZZ,
30 2 GAMA, NEL, LFT, LLT,
31 3 ISORTH)
32C-----------------------------------------------
33C I m p l i c i t T y p e s
34C-----------------------------------------------
35#include "implicit_f.inc"
36C-----------------------------------------------
37C G l o b a l P a r a m e t e r s
38C-----------------------------------------------
39#include "mvsiz_p.inc"
40C-----------------------------------------------
41C D u m m y A r g u m e n t s
42C-----------------------------------------------
43 INTEGER, INTENT(INOUT) :: LFT
44 INTEGER, INTENT(INOUT) :: LLT
45 INTEGER, INTENT(INOUT) :: ISORTH
46 INTEGER NEL
47C REAL
49 . reploc(nel,6),wxx(*), wyy(*), wzz(*), gama(mvsiz,6)
50C-----------------------------------------------
51C C o m m o n B l o c k s
52C-----------------------------------------------
53C-----------------------------------------------
54C L o c a l V a r i a b l e s
55C-----------------------------------------------
56 INTEGER I, J
57C REAL
58 my_real
59 . rx(mvsiz),ry(mvsiz),rz(mvsiz),cr(mvsiz),sr(mvsiz),
60 . nr,ps,ux,uy,uz,vx,vy,vz,wx,wy,wz,tx,ty,tz
61C-----------------------------------------------
62 IF (isorth == 0) THEN
63 DO i=lft,llt
64 gama(i,1)=one
65 gama(i,2)=zero
66 gama(i,3)=zero
67 gama(i,4)=zero
68 gama(i,5)=one
69 gama(i,6)=zero
70 ENDDO
71 ELSE
72C
73 DO i=lft,llt
74 nr=sqrt(wxx(i)*wxx(i)+wyy(i)*wyy(i)+wzz(i)*wzz(i))
75 cr(i)=one-half*nr*nr
76 sr(i)=nr
77 nr=one/max(em20,nr)
78 rx(i)=wxx(i)*nr
79 ry(i)=wyy(i)*nr
80 rz(i)=wzz(i)*nr
81 ENDDO
82C
83 DO i=lft,llt
84 ux=reploc(i,1)
85 uy=reploc(i,2)
86 uz=reploc(i,3)
87 ps=ux*rx(i)+uy*ry(i)+uz*rz(i)
88 vx=ps*rx(i)
89 vy=ps*ry(i)
90 vz=ps*rz(i)
91 wx=ux-vx
92 wy=uy-vy
93 wz=uz-vz
94 tx=ry(i)*wz-rz(i)*wy
95 ty=rz(i)*wx-rx(i)*wz
96 tz=rx(i)*wy-ry(i)*wx
97 ux=vx+cr(i)*wx+sr(i)*tx
98 uy=vy+cr(i)*wy+sr(i)*ty
99 uz=vz+cr(i)*wz+sr(i)*tz
100 nr=one/max(em20,sqrt(ux*ux+uy*uy+uz*uz))
101 reploc(i,1)=ux*nr
102 reploc(i,2)=uy*nr
103 reploc(i,3)=uz*nr
104 ENDDO
105C
106 DO i=lft,llt
107 ux=reploc(i,4)
108 uy=reploc(i,5)
109 uz=reploc(i,6)
110 ps=ux*rx(i)+uy*ry(i)+uz*rz(i)
111 vx=ps*rx(i)
112 vy=ps*ry(i)
113 vz=ps*rz(i)
114 wx=ux-vx
115 wy=uy-vy
116 wz=uz-vz
117 tx=ry(i)*wz-rz(i)*wy
118 ty=rz(i)*wx-rx(i)*wz
119 tz=rx(i)*wy-ry(i)*wx
120 ux=vx+cr(i)*wx+sr(i)*tx
121 uy=vy+cr(i)*wy+sr(i)*ty
122 uz=vz+cr(i)*wz+sr(i)*tz
123 nr=one/max(em20,sqrt(ux*ux+uy*uy+uz*uz))
124 reploc(i,4)=ux*nr
125 reploc(i,5)=uy*nr
126 reploc(i,6)=uz*nr
127 ENDDO
128C
129 DO i=lft,llt
130 gama(i,1)=reploc(i,1)
131 gama(i,2)=reploc(i,2)
132 gama(i,3)=reploc(i,3)
133 gama(i,4)=reploc(i,4)
134 gama(i,5)=reploc(i,5)
135 gama(i,6)=reploc(i,6)
136 ENDDO
137C
138 ENDIF
139C
140 RETURN
141 END
#define my_real
Definition cppsort.cpp:32
#define max(a, b)
Definition macros.h:21
subroutine spreploc(reploc, wxx, wyy, wzz, gama, nel, lft, llt, isorth)
Definition spreploc.F:32