-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathMatOp.f90
79 lines (69 loc) · 4.06 KB
/
MatOp.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
Subroutine MatOp(a,b,dt,HydroParam,MeshParam)
! Compute the Semi-Implicit Method Coefficient Matrix
!
! [1] Casulli, V. A high-resolution wetting and drying algorithm for free-surfacehydrodynamics.
! International Journal for Numerical Methods in Fluids, v. 60, n. 4 (2009), p. 391-408
! [2] Casulli, Vincenzo. A conservative semi‐implicit method for coupled surface–subsurface flows in regional scale.
! International Journal for Numerical Methods in Fluids, v. 79, n. 4 (2015), p. 199-214.
! Input:
! a -> Free-Surface Elevation Vector
! Output:
! b -> Solution
! List of Modifications:
! -> 10.03.2014: Routine Implementation (Rafael Cavalcanti)
! -> 07.05.2019: Update - Subsurface Flow Term (Cayo Lopes)
! Programmer: Rafael Cavalcanti
!$ use omp_lib
Use MeshVars
Use Hydrodynamic
Implicit None
Integer:: iElem, iEdge, Pij, Face
Real:: Sum1, Coef
Real:: NearZero = 1e-10
Real:: dt
type(MeshGridParam) :: MeshParam
type(HydrodynamicParam) :: HydroParam
Real, intent(in) :: a(MeshParam%nElem)
Real, intent(out) :: b(MeshParam%nElem)
Real:: aGhost
!Coef = HydroParam%g*(HydroParam%Theta*dt)**2
!call omp_set_num_threads(1)
! 1. Compute T Matrix (Casulli, 2009)
!!$OMP parallel do default(none) shared(a,b,MeshParam,HydroParam,NearZero,Coef) private(iElem,iEdge,Face,Pij,Sum)
Do iElem = 1, MeshParam%nElem
b(iElem) = (HydroParam%P(iElem)-HydroParam%Qk(iElem))*a(iElem) !Initializing b vector
Sum1 = 0.d0
Do iEdge = 1,4
Face = MeshParam%Edge(iEdge,iElem)
Pij = MeshParam%Neighbor(iEdge,iElem)
If (HydroParam%IndexWaterLevelEdge(Face)>0) Then
!Face with pressure head boundary condition:
!!Casulli,2015:
Sum1 = Sum1 + ( MeshParam%EdgeLength(Face)/MeshParam%CirDistance(Face) )*( - a(iElem) )*(HydroParam%Theta*dt)*(HydroParam%Theta*HydroParam%g*dt*HydroParam%DZiADZ(Face) + HydroParam%DZK(Face))
!Sum1 = Sum1 + ( MeshParam%EdgeLength(Face)/MeshParam%CirDistance(Face) )*( - a(iElem) )*((HydroParam%Theta*dt)*HydroParam%Theta*HydroParam%g*dt*HydroParam%DZiADZ(Face) + HydroParam%DZK(Face)*dt)
!Sum1 = Sum1 + ( MeshParam%EdgeLength(Face)/MeshParam%CirDistance(Face) )*( - a(iElem) )*(HydroParam%Theta*dt)*(HydroParam%Theta*HydroParam%g*dt*HydroParam%DZiADZ(Face) + HydroParam%Theta*HydroParam%DZK(Face))
Else
If (Pij == 0) Then
Sum1 = Sum1
continue
Else
!Casulli,2015:
Sum1 = Sum1 + ( MeshParam%EdgeLength(Face)/MeshParam%CirDistance(Face) )*( ( a(Pij) - a(iElem) ) )*(HydroParam%Theta*dt)*(HydroParam%Theta*HydroParam%g*dt*HydroParam%DZiADZ(Face) + HydroParam%DZK(Face))
!Sum1 = Sum1 + ( MeshParam%EdgeLength(Face)/MeshParam%CirDistance(Face) )*( ( a(Pij) - a(iElem) ) )*(HydroParam%Theta*dt*HydroParam%Theta*HydroParam%g*dt*HydroParam%DZiADZ(Face) + dt*HydroParam%DZK(Face))
!Sum1 = Sum1 + ( MeshParam%EdgeLength(Face)/MeshParam%CirDistance(Face) )*( ( a(Pij) - a(iElem) ) )*(HydroParam%Theta*dt)*(HydroParam%Theta*HydroParam%g*dt*HydroParam%DZiADZ(Face) + HydroParam%Theta*HydroParam%DZK(Face))
EndIf
EndIf
!If (Pij == 0.or.HydroParam%H(Face) <= HydroParam%PCRI+NearZero) Then
! If (HydroParam%IndexWaterLevel(iElem)>0) Then
! Sum1 = Sum1 + Coef*( MeshParam%EdgeLength(Face)/MeshParam%CirDistance(Face) )*( ( - a(iElem) ) )*HydroParam%DZiADZ(Face) !( EdgeLength(Face)/CirDistance(Face) )*
! EndIf
!Else
! Sum1 = Sum1 + Coef*( MeshParam%EdgeLength(Face)/MeshParam%CirDistance(Face) )*( ( a(Pij) - a(iElem) ) )*HydroParam%DZiADZ(Face)
!EndIf
EndDo
!b(iElem) = (P+T).eta
b(iElem) = b(iElem) - Sum1
EndDo
!!$OMP end parallel do
Return
End Subroutine MatOp