OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
gradient_limitation2.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!|| gradient_limitation2 ../engine/source/ale/alemuscl/gradient_limitation2.F
25!||--- called by ------------------------------------------------------
26!|| ale51_gradient_reconstruction2 ../engine/source/ale/alemuscl/ale51_gradient_reconstruction2.F
27!||--- uses -----------------------------------------------------
28!|| alemuscl_mod ../common_source/modules/ale/alemuscl_mod.F
29!||====================================================================
30 SUBROUTINE gradient_limitation2(IXQ, X, TRIMAT)
31C-----------------------------------------------
32C D e s c r i p t i o n
33C limits the amplitude of this gradient in such a way that
34C extrapolated values on the nodes of the element lie between
35C local minimum and maximum values from the neighboring elements
36C -> maximum principle purpose
37C-----------------------------------------------
38C M o d u l e s
39C-----------------------------------------------
40 USE alemuscl_mod
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 "vect01_c.inc"
49#include "com04_c.inc"
50C-----------------------------------------------
51C D u m m y A r g u m e n t s
52C-----------------------------------------------
53 INTEGER, INTENT(IN) :: IXQ(NIXQ, NUMELQ), TRIMAT
54 my_real, INTENT(IN) :: x(3,numnod)
55C-----------------------------------------------
56C L o c a l V a r i a b l e s
57C-----------------------------------------------
58 INTEGER :: I, II, JJ
59 INTEGER :: NODE_ID
60 my_real :: reduc_factor(trimat), nodal_reduc_factor, yn, zn, valnode
61 INTEGER :: ITRIMAT
62 INTEGER :: NNUM
63 my_real :: yk, zk
64C-----------------------------------------------
65C S o u r c e L i n e s
66C-----------------------------------------------
67 !!! Limiting process for the computed gradient -> maximum principle
68 !!! and stability purposes
69 DO i = lft, llt
70 ii = i + nft
71 !!! Element centroid
72 yk = alemuscl_buffer%ELCENTER(ii,2) ; zk = alemuscl_buffer%ELCENTER(ii,3)
73 reduc_factor = ep30
74 nnum = 0
75 DO itrimat = 1, trimat
76 IF(abs(alemuscl_buffer%GRAD(ii,2,itrimat)) +
77 . abs(alemuscl_buffer%GRAD(ii,3,itrimat)) > zero) THEN
78 nnum = nnum + 1
79 !!! Check the nodes of the element
80 DO jj = 1, 4
81 node_id = ixq(jj+1, ii)
82 !!! Get the node coordinates
83 yn = x(2, node_id) ; zn = x(3, node_id)
84 !!! Interpolate the function at the node
85 valnode = alemuscl_buffer%VOLUME_FRACTION(ii,itrimat)
86 . + alemuscl_buffer%GRAD(ii,2,itrimat) * (yn - yk)
87 . + alemuscl_buffer%GRAD(ii,3,itrimat) * (zn - zk)
88 nodal_reduc_factor = one
89 IF (valnode - alemuscl_buffer%VOLUME_FRACTION(ii,itrimat) > zero) THEN
90 nodal_reduc_factor =
91 . min((alemuscl_buffer%NODE_MAX_VALUE(node_id,itrimat) - alemuscl_buffer%VOLUME_FRACTION(ii,itrimat))
92 . / (valnode - alemuscl_buffer%VOLUME_FRACTION(ii,itrimat)), alemuscl_param%BETA)
93 ELSE IF (valnode - alemuscl_buffer%VOLUME_FRACTION(ii,itrimat) < zero) THEN
94 nodal_reduc_factor =
95 . min((alemuscl_buffer%NODE_MIN_VALUE(node_id,itrimat) - alemuscl_buffer%VOLUME_FRACTION(ii,itrimat))
96 . / (valnode - alemuscl_buffer%VOLUME_FRACTION(ii,itrimat)), alemuscl_param%BETA)
97 ENDIF
98 reduc_factor(itrimat) = min(reduc_factor(itrimat), nodal_reduc_factor)
99 ENDDO ! JJ = 1, 8
100 ELSE
101 reduc_factor(itrimat) = zero
102 ENDIF
103 ENDDO ! ITRIMAT = 1, TRIMAT
104
105 DO itrimat = 1, trimat
106 IF(abs(alemuscl_buffer%GRAD(ii,2,itrimat)) + abs(alemuscl_buffer%GRAD(ii,3,itrimat)) > zero) THEN
107 !!! Limitation of the gradient
108 alemuscl_buffer%GRAD(ii,2,itrimat) = reduc_factor(itrimat) * alemuscl_buffer%GRAD(ii,2,itrimat)
109 alemuscl_buffer%GRAD(ii,3,itrimat) = reduc_factor(itrimat) * alemuscl_buffer%GRAD(ii,3,itrimat)
110 ENDIF
111 ENDDO
112 ENDDO ! I = LFT, LLT
113C-----------------------------------------------
114 END SUBROUTINE gradient_limitation2
#define my_real
Definition cppsort.cpp:32
subroutine gradient_limitation2(ixq, x, trimat)
#define min(a, b)
Definition macros.h:20
type(alemuscl_param_) alemuscl_param
type(alemuscl_buffer_) alemuscl_buffer