OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
conjugate_gradient.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!|| cg ../engine/source/ale/alemuscl/conjugate_gradient.F
25!||--- called by ------------------------------------------------------
26!|| gradient_reconstruction ../engine/source/ale/alemuscl/gradient_reconstruction.F
27!||====================================================================
28 SUBROUTINE cg (dim, mat, rhs, sol, max_iter, tol)
29C-----------------------------------------------
30C D e s c r i p t i o n
31C This subroutine computes the solution to the linear system
32C mat * sol = rhs by the conjugate gradient method.
33C This assumes that mat is a symmetric positive matrix
34C-----------------------------------------------
35
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, INTENT(IN) :: dim ! system dimension
44 my_real, INTENT(INOUT) :: mat(dim, dim) ! matrix
45 my_real, INTENT(INOUT) :: rhs(dim) ! right hand side
46 my_real, INTENT(OUT) :: sol(dim) ! solution vector
47 INTEGER, INTENT(IN) :: max_iter
48 my_real, INTENT(IN) :: tol
49C-----------------------------------------------
50C L o c a l V a r i a b l e s
51C-----------------------------------------------
52 INTEGER ii ! matrix and vector indexes
53 INTEGER iter ! iteration count
54 my_real error, norm_init ! error, initial norm
55 my_real :: r(dim), rnew(dim), p(dim), temp(dim)
56 my_real :: alpha, beta
57C-----------------------------------------------
58C S o u r c e L i n e s
59C-----------------------------------------------
60!!! Setting the solution vector to zero
61 sol(1:dim) = zero
62!!! Initialization of the algorithm
63 r(1:dim) = rhs(1:dim) - matmul(mat(1:dim, 1:dim), sol(1:dim))
64 p(1:dim) = r(1:dim)
65 norm_init = maxval(abs(r(1:dim)))
66 error = norm_init
67 iter = 0
68
69!!! Main loop
70 DO WHILE ((iter < max_iter) .AND. (error > tol))
71 !DO WHILE (iter < max_iter)
72 iter = iter + 1
73 temp(1:dim) = matmul(mat(1:dim, 1:dim), p(1:dim))
74 alpha = dot_product(r(1:dim), r(1:dim)) / dot_product(temp(1:dim), p(1:dim))
75 DO ii = 1, dim
76 sol(ii) = sol(ii) + alpha * p(ii)
77 rnew(ii) = r(ii) - alpha * temp(ii)
78 ENDDO
79 beta = dot_product(rnew(1:dim), rnew(1:dim)) / dot_product(r(1:dim), r(1:dim))
80 DO ii = 1, dim
81 p(ii) = rnew(ii) + beta * p(ii)
82 r(ii) = rnew(ii)
83 ENDDO
84 error = maxval(abs(r(1:dim))) / norm_init
85 ENDDO
86
87 IF (error > tol) THEN
88C PRINT*, "GC NON CONVERGENCE"
89 ENDIF
90
91C-----------------------------------------------
92 END SUBROUTINE cg
subroutine cg(dim, mat, rhs, sol, max_iter, tol)
#define my_real
Definition cppsort.cpp:32
#define alpha
Definition eval.h:35