-
Notifications
You must be signed in to change notification settings - Fork 0
/
CGOpNH_leo.f90
87 lines (80 loc) · 3.29 KB
/
CGOpNH_leo.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
Subroutine CGOpNH(a,b,dt,HydroParam,MeshParam)
! Matrix Free Conjugate Gradient Method
! Input:
! a -> Input Matrix
! Output:
! b -> Solution
! List of Modifications:
! -> 10.03.2014: Routine Implementation (Rafael Cavalcanti)
! -> 10.03.2014: Fortran Sintax (Rafael Cavalcanti)
! Programmer: Michael Dumbser
Use MeshVars !, Only: nElem, Edge, Neighbor, EdgeLength, Cirdistance
Use Hydrodynamic
!Use SimulationModel, Only: dt,NearZero
Implicit None
Double Precision:: alpha, tol, lambda, alphanew
Integer:: k, N
Integer:: iElem, iEdge,iLayer, Pij, Face
Double Precision:: Soma, Coef
Double Precision:: NearZero = 1e-10
Double Precision:: dt
type(MeshGridParam) :: MeshParam
type(HydrodynamicParam) :: HydroParam
Double Precision, intent(in) :: a(MeshParam%kMax+1,MeshParam%nElem)
Double Precision, intent(out) :: b(MeshParam%kMax+1,MeshParam%nElem)
Double Precision:: r(MeshParam%kMax+1,MeshParam%nElem), Ab(MeshParam%kMax+1,MeshParam%nElem), pCG(MeshParam%kMax+1,MeshParam%nElem), v(MeshParam%kMax+1,MeshParam%nElem)
N = MeshParam%nElem
b = a ! Initial guess
Call MatOpNH(b,Ab,dt,HydroParam,MeshParam)
Do iElem = 1, MeshParam%nElem
Do iLayer = HydroParam%ElSmallm(iElem), HydroParam%ElCapitalM(iElem)+1
r(iLayer,iElem) = b(iLayer,iElem) - Ab(iLayer,iElem)
EndDo
EndDo
pCG = r ! Steepest Descent Direction
alpha = 0.
Do iElem = 1, MeshParam%nElem
Do iLayer = HydroParam%ElSmallm(iElem), HydroParam%ElCapitalM(iElem)+1
alpha = alpha + r(iLayer,iElem)*r(iLayer,iElem)
EndDo
EndDo
tol = 1e-20 ! Tolerance
Do k = 1,1000*N
If ( sqrt(alpha) < tol ) Then
! System has been solved
!Print*, 'The system has been solved with: ',k, 'CGOp iterations'
Return
EndIf
Call MatOpNH(pCG,v,dt,HydroParam,MeshParam)
Soma = 0.
Do iElem = 1, MeshParam%nElem
Do iLayer = HydroParam%ElSmallm(iElem), HydroParam%ElCapitalM(iElem)+1
Soma = Soma + pCG(iLayer,iElem)*v(iLayer,iElem)
EndDo
EndDo
lambda = alpha/Soma
Do iElem = 1, MeshParam%nElem
Do iLayer = HydroParam%ElSmallm(iElem), HydroParam%ElCapitalM(iElem)+1
b(iLayer,iElem) = b(iLayer,iElem) + lambda*pCG(iLayer,iElem)
EndDo
EndDo
Do iElem = 1, MeshParam%nElem
Do iLayer = HydroParam%ElSmallm(iElem), HydroParam%ElCapitalM(iElem)+1
r(iLayer,iElem) = r(iLayer,iElem) - lambda*v(iLayer,iElem)
EndDo
EndDo
alphanew = 0.
Do iElem = 1, MeshParam%nElem
Do iLayer = HydroParam%ElSmallm(iElem), HydroParam%ElCapitalM(iElem)+1
alphanew = alphanew + r(iLayer,iElem)*r(iLayer,iElem)
EndDo
EndDo
Do iElem = 1, MeshParam%nElem
Do iLayer = HydroParam%ElSmallm(iElem), HydroParam%ElCapitalM(iElem)+1
pCG(iLayer,iElem) = r(iLayer,iElem) + alphanew/alpha*pCG(iLayer,iElem)
EndDo
EndDo
alpha = alphanew
EndDo
Return
End Subroutine CGOpNH