OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
aturi2.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/.
23C
24!||====================================================================
25!|| aturi2 ../starter/source/ale/ale2d/aturi2.F
26!||--- called by ------------------------------------------------------
27!|| binit2 ../starter/source/ale/bimat/binit2.F
28!|| q4init2 ../starter/source/elements/solid_2d/quad4/q4init2.F
29!|| qinit2 ../starter/source/elements/solid_2d/quad/qinit2.F
30!||====================================================================
31 SUBROUTINE aturi2(IPARG,RHO,PM,IX,X,RK,RE,AIRE)
32C-----------------------------------------------
33C D e s c r i p t i o n
34C-----------------------------------------------
35C This subroutine is initializing state for
36C turbulency model K-EPS in ALE (2D)
37C-----------------------------------------------
38C I m p l i c i t T y p e s
39C-----------------------------------------------
40#include "implicit_f.inc"
41C-----------------------------------------------
42C G l o b a l P a r a m e t e r s
43C-----------------------------------------------
44#include "mvsiz_p.inc"
45C-----------------------------------------------
46C C o m m o n B l o c k s
47C-----------------------------------------------
48#include "com01_c.inc"
49#include "vect01_c.inc"
50#include "param_c.inc"
51#include "com04_c.inc"
52C-----------------------------------------------
53C D u m m y A r g u m e n t s
54C-----------------------------------------------
55 INTEGER IPARG(NPARG,NGROUP), IX(7,*)
56 my_real, INTENT(INOUT) :: x(3,numnod), rk(mvsiz), re(mvsiz)
57 my_real, INTENT(IN) :: rho(mvsiz),pm(npropm,nummat), aire(mvsiz)
58C-----------------------------------------------
59C L o c a l V a r i a b l e s
60C-----------------------------------------------
61 INTEGER I, II, MAT, NG, MTN2, LLT2, NFT2, LFT2, JJ, J
62 my_real xl, xk, c1, xe, d2, y0, z0, y1, z1
63C-----------------------------------------------
64C S o u r c e L i n e s
65C-----------------------------------------------
66 IF(mtn == 17)THEN
67 DO i=lft,llt
68 ii=i+nft
69 mat=iabs(ix(1,ii))
70 rk(i)=rho(i)*pm(87,mat)
71 xl=sqrt(aire(i))
72 xk= max(rk(i),em15)/rho(i)
73 c1=pm(81,mat)
74 xe=sqrt(xk*sqrt(c1))**3/(zep4187*xl)
75 re(i)=rho(i)*xe
76 END DO
77 ELSE
78 DO i=lft,llt
79 ii=i+nft
80 mat=iabs(ix(1,ii))
81 rk(i)=rho(i)*pm(87,mat)
82 xl=sqrt(aire(i))
83 xk= max(rk(i),em15)/rho(i)
84 d2=ep30
85 y0=x(2,ix(2,ii))+x(2,ix(3,ii))+x(2,ix(4,ii))+x(2,ix(5,ii))
86 z0=x(3,ix(2,ii))+x(3,ix(3,ii))+x(3,ix(4,ii))+x(3,ix(5,ii))
87 DO ng=1,ngroup
88 mtn2=iparg(1,ng)
89 IF(mtn2 == 17)THEN
90 llt2=iparg(2,ng)
91 nft2=iparg(3,ng)
92 lft2=1
93 DO jj=lft2,llt2
94 j=jj+nft2
95 y1=x(2,ix(2,j))+x(2,ix(3,j))+x(2,ix(4,j))+x(2,ix(5,j))
96 z1=x(3,ix(2,j))+x(3,ix(3,j))+x(3,ix(4,j))+x(3,ix(5,j))
97 d2= min(d2,(y1-y0)**2+(z1-z0)**2)
98 END DO !JJ=LFT2,LLT2
99 ENDIF
100 END DO !NG=1,NGROUP
101 xl=xl+ fourth*sqrt(d2)
102 xe=zep33*sqrt(xk)**3/xl
103 re(i)=rho(i)*xe
104 END DO !I=LFT,LLT
105 ENDIF
106C-----------------------------------------------
107 RETURN
108 END
subroutine aturi2(iparg, rho, pm, ix, x, rk, re, aire)
Definition aturi2.F:32
#define my_real
Definition cppsort.cpp:32
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21