-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathAlgebricMod.f90
115 lines (99 loc) · 3.25 KB
/
AlgebricMod.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
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
module AlgebricMod
use constants, only : pi
use Structures, only : grid_object ! import node type from Structures module
implicit none
private ! declare that all things not declared public are private
public :: genAlgebric ! declare public
integer :: Imax, Jmax, i, j
contains
! define x at Left boundary at j
function xL() result(retval)
implicit none
! integer, intent(in):: j
real :: retval
retval = 0
end function xL
! define x at Right boundary at j
function xR() result(retval)
implicit none
! integer, intent(in):: j
real(8) :: retval
retval = 5
end function xR
! define y at Upper boundary at i
function yU() result(retval)
implicit none
! integer, intent(in):: i
real(8) :: retval
retval = 1
end function yU
! define y at Lower boundary at i
function yL(i) result(retval)
implicit none
integer, intent(in) :: i
real(8) :: temp_x, retval
temp_x = x_function(i)
if ((temp_x >= 0 .and. temp_x <= 2) .or. (temp_x >= 3 .and. temp_x <= 5)) then
retval = 0
else if (temp_x > 2 .and. temp_x < 3) then
retval = 0.10d0 * sin((temp_x-2)*pi)
end if
end function yL
! calculate zeta at i
function zeta(i) result(retval)
implicit none
integer, intent(in) :: i
real(8) :: retval
retval = real(i-1)/real(Imax-1)
end function zeta
! calculate eta at i
function eta(j) result(retval)
implicit none
integer, intent(in) :: j
real(8) :: retval
retval = real(j-1,8)/real(Jmax-1,8)
end function eta
! calculate x at i
function x_function(i) result(retval)
implicit none
integer, intent(in) :: i
real(8) :: retval
retval = xL() + zeta(i) * (xR() - xL())
end function x_function
! calculate y at i & j
function y_function(i, j) result(retval)
implicit none
integer, intent(in) :: i, j
real(8) :: retval
retval = yL(i) + eta(j) * (yU() - yL(i))
end function y_function
! generate the algebric grid (Imax x Jmax) nodes
subroutine genAlgebric(AlgGrid)
implicit none
type(grid_object) :: AlgGrid
real(8), dimension(:), allocatable :: temp
integer :: MinIndex
Imax = AlgGrid%Imax
Jmax = AlgGrid%Jmax
do i = 1, Imax
do j = 1, Jmax
AlgGrid%nodes(i,j)%n = i + (j-1) * Imax
AlgGrid%nodes(i,j)%zeta = zeta(i)
AlgGrid%nodes(i,j)%eta = eta(j)
AlgGrid%nodes(i,j)%x = x_function(i)
AlgGrid%nodes(i,j)%y = y_function(i,j)
end do
end do
! fix position of LE
allocate(temp(Imax))
temp = abs(AlgGrid%nodes(:,1)%x - 2)
MinIndex = MINLOC(temp, 1)
AlgGrid%nodes(MinIndex,1)%x = 2.0d0
AlgGrid%nodes(MinIndex,1)%y = 0.0d0
! fix position of TE
temp = abs(AlgGrid%nodes(:,1)%x - 3)
MinIndex = MINLOC(temp, 1)
AlgGrid%nodes(MinIndex,1)%x = 3.0d0
AlgGrid%nodes(MinIndex,1)%y = 0.0d0
end subroutine genAlgebric
end module AlgebricMod