ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
ets_math.f90
Go to the documentation of this file.
1 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
2 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
3 !-------------------------------------------------------!
4 ! !
5 !____________ ETS MATHEMATICAL SUBROUTINES: ___________!
6 ! !
7 !-------------------------------------------------------!
8 ! These subroutines are aimed to provide the transport !
9 ! solver with the simple mathematics !
10 !-------------------------------------------------------!
11 MODULE ets_math
12 CONTAINS
13 
14 
15 
16 
17 !-------------------------------------------------------!
18 !-------------------------------------------------------!
19 SUBROUTINE deriv_fun(N, X, Y, DY)
20 !-------------------------------------------------------!
21 ! These subroutine calculate the derivative, DY !
22 ! of the function Y with respect to argument X !
23 !-------------------------------------------------------!
24 
25  USE itm_types
26 
27  IMPLICIT NONE
28 
29  INTEGER :: n ! number of radial points (input)
30  INTEGER :: i ! radial index
31 
32  REAL (R8) :: x(n) ! argument array (input)
33  REAL (R8) :: y(n) ! function array (input)
34  REAL (R8) :: dy(n) ! function derivative array (output)
35  REAL (R8) :: h(n)
36 
37 
38  DO i=1,n-1
39  h(i)=x(i+1)-x(i)
40  END DO
41 
42  DO i=2,n-1
43  dy(i) = ((y(i+1)-y(i))*h(i-1)/h(i) + (y(i)-y(i-1))*h(i)/h(i-1)) / (h(i)+h(i-1))
44  END DO
45 
46  dy(1) = dy(2) - 2.e0_r8*((y(1)-y(2))/h(1)+(y(3)-y(2))/h(2))/(h(2)+h(1)) * h(1)
47 
48  dy(n) = dy(n-1)+ 2.e0_r8*((y(n-2)-y(n-1))/h(n-2)+(y(n)-y(n-1))/h(n-1))/(h(n-1)+h(n-2)) * h(n-1)
49 ! DY(N) = (Y(N)-Y(N-1))/H(N-1)
50 
51  RETURN
52 
53 END SUBROUTINE deriv_fun
54 !-------------------------------------------------------!
55 !-------------------------------------------------------!
56 
57 
58 
59 
60 
61 !-------------------------------------------------------!
62 !-------------------------------------------------------!
63 SUBROUTINE integr_fun(N,X,Y,INTY)
64 !-------------------------------------------------------!
65 ! This subroutine calculates integral of function !
66 ! Y(X) from X=0 until X=X(N) !
67 !-------------------------------------------------------!
68 
69  USE itm_types
70 
71  IMPLICIT NONE
72  INTEGER :: n ! number of radial points (input)
73  INTEGER :: i
74 
75  REAL (R8) :: x(n) ! argument array (input)
76  REAL (R8) :: y(n) ! function array (input)
77  REAL (R8) :: inty(n) ! function integral array (output)
78 
79 
80  inty(1) = y(1)*x(1)/2.e0_r8
81  DO i=2,n
82  inty(i) = inty(i-1)+(y(i-1)+y(i))*(x(i)-x(i-1))/2.e0_r8
83  END DO
84 
85  RETURN
86 
87 END SUBROUTINE integr_fun
88 !-------------------------------------------------------!
89 !-------------------------------------------------------!
90 
91 
92 
93 
94 
95 !-------------------------------------------------------!
96 !-------------------------------------------------------!
97 SUBROUTINE integr_xfun(N,X,Y,INTXY)
98 !-------------------------------------------------------!
99 ! This subroutine calculates integral of function !
100 ! Y(X)*X from X=0 until X=X(N) !
101 !-------------------------------------------------------!
102 
103  USE itm_types
104 
105  IMPLICIT NONE
106  INTEGER :: n ! number of radial points (input)
107  INTEGER :: i
108 
109  REAL (R8) :: x(n) ! argument array (input)
110  REAL (R8) :: y(n) ! function array (input)
111  REAL (R8) :: intxy(n) ! function integral array (output)
112 
113  intxy(1) = y(1)*x(1)**2/2.e0_r8
114  DO i=2,n
115  intxy(i) = intxy(i-1)+(y(i-1)*x(i-1)+y(i)*x(i))*(x(i)-x(i-1))/2.e0_r8
116  END DO
117 
118  RETURN
119 END SUBROUTINE integr_xfun
120 !-------------------------------------------------------!
121 !-------------------------------------------------------!
122 
123 
124 
125 
126 
127 !-------------------------------------------------------!
128 !-------------------------------------------------------!
129 SUBROUTINE fix_axis_value(GEOMETRY,PROFILE,N)
130 !-------------------------------------------------------!
131 ! !
132 ! This subroutine shall fix central points of PROFILE !
133 ! from (1) to (N) using parabolic approximation !
134 ! !
135 !-------------------------------------------------------!
136  USE itm_types
137  USE itm_constants
138  USE ets_plasma
139 
140  IMPLICIT NONE
141 
142 
143 ! +++ Plasma parameters:
144  TYPE (magnetic_geometry) :: geometry
145  REAL (R8) :: profile(geometry%nrho)
146  REAL (R8) :: a, b, c
147  REAL (R8) :: x(n+2)
148  INTEGER :: i,n
149 
150  DO i = 1,n+2
151  x(i) = geometry%RHO(i)
152  END DO
153 
154  a = (profile(n)-profile(n+2))/(x(n)-x(n+2))/x(n+1)/2.0_r8
155  c = profile(n+1) - a*x(n+1)**2.0_r8
156 
157  DO i = 1,n
158  profile(i) = a*x(i)**2.0_r8 + c
159  END DO
160 
161  RETURN
162 END SUBROUTINE fix_axis_value
163 !-------------------------------------------------------!
164 !-------------------------------------------------------!
165 
166 
167 
168 END MODULE ets_math
subroutine integr_xfun(N, X, Y, INTXY)
Definition: ets_math.f90:97
subroutine deriv_fun(N, X, Y, DY)
Definition: ets_math.f90:19
subroutine fix_axis_value(GEOMETRY, PROFILE, N)
Definition: ets_math.f90:129
real(r8) function, dimension(1:size(x)) profile(function_string, x)
subroutine integr_fun(N, X, Y, INTY)
Definition: ets_math.f90:63
The module declares types of variables used in ETS (transport code)
Definition: ets_plasma.f90:8