ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
solution_interface.f90
Go to the documentation of this file.
1 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
10 ! + + + + + + INTERFACE TO NUMERICAL SOLVER + + + + + + +
11 
12  SUBROUTINE solution_interface (SOLVER, ifail)
13 
14 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
15 ! This interface is prepared to test the ETS +
16 ! and will be replaced by KEPLER +
17 ! +
18 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
19 ! Source: -- +
20 ! Developers: D.Kalupin +
21 ! Kontacts: D.Kalupin@fz-juelich.de +
22 ! +
23 ! Comments: should be replaced by KEPLER +
24 ! +
25 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
26 
27 
28  USE ets_plasma
29  USE type_solver
30  USE itm_types
31  USE ets_math
32 
33  IMPLICIT NONE
34 
35 
36  TYPE (numerics), INTENT (INOUT) :: solver
37  INTEGER, INTENT (INOUT) :: ifail
38  INTEGER :: i
39  REAL (R8) :: fun(solver%nrho)
40  REAL (R8) :: dfun(solver%nrho)
41  REAL (R8) :: intfun(solver%nrho)
42  LOGICAL, parameter :: debug = .true.
43 
44 
45 
46 ! + + + + + + + + + INTERFACE PART + + + + + + + + + + +
47 
48  choose_numerical_solver: IF (solver%TYPE.EQ.1) THEN
49 ! call numerical solver extracted from RITM, with differential form of equation
50  CALL solution1(solver, ifail)
51 
52  ELSE IF (solver%TYPE.EQ.2) THEN
53 ! call numerical solver extracted from RITM, with integral form of equation
54  CALL solution2(solver, ifail)
55 
56  ELSE IF (solver%TYPE.EQ.3) THEN
57 ! call matrix numerical solver extracted from COREDIF
58  CALL solution3(solver, ifail)
59 
60  ELSE IF (solver%TYPE.EQ.4) THEN
61 ! call the improved solver 3 (progonka/block thomas) from Roman Stankiewicz
62  CALL solution4(solver, ifail)
63 
64  ELSE IF (solver%TYPE.EQ.6) THEN
65 ! call solver from Guido Huysmans
66  CALL solution6(solver, ifail)
67 
68  ELSE IF (solver%TYPE.EQ.7 .OR. solver%TYPE.EQ.8) THEN
69 ! call numerical solver extracted from RITM, with differential form of equation
70  CALL solution7(solver, ifail)
71 
72  ELSE IF (solver%TYPE.EQ.9) THEN
73 ! call solver from Guido Huysmans
74 ! CALL SOLUTION9 (SOLVER, ifail)
75 
76  ELSE IF (solver%TYPE.EQ.10) THEN
77 ! call solver from CRONOS
78  CALL solution10(solver, ifail)
79 
80  ELSE IF (solver%TYPE.EQ.11) THEN
81 ! call solver from FESB (Anna Šušnjara)
82  CALL solutionfem(solver, ifail)
83 
84  ELSE
85  WRITE(*,*) 'Invalid SOLVER%TYPE = ',solver%TYPE
86  END IF choose_numerical_solver
87 
88  IF (ifail.GT.2) ifail = 0
89 
90 
91 
92 
93  check_derivative: DO i = 1,solver%NDIM
94  derivative_recalculate: IF (solver%DERIVATIVE_FLAG(i).EQ.1) THEN
95  fun(:) = solver%Y(i,:)
96  CALL deriv_fun(solver%NRHO, solver%RHO, fun, dfun)
97  solver%DY(i,:) = dfun(:)
98 
99  ELSE IF (solver%DERIVATIVE_FLAG(i).EQ.2) THEN
100  fun(:) = solver%C(i,:) &
101  *((solver%F(i,:) + solver%B(i,:)*solver%YM(i,:)/solver%H) &
102  -(solver%G(i,:) + solver%A(i,:)/solver%H)*solver%Y(i,:))
103 
104  CALL integr_fun(solver%NRHO, solver%RHO, fun, intfun)
105 
106  solver%DY(i,:) = (solver%E(i,:)*solver%Y(i,:)-intfun(:)) / solver%D(i,:)
107 
108  check_inner_boundary: IF (solver%V(i,1).NE.0.0_r8) THEN
109  solver%DY(i,1) = (solver%W(i,1) - solver%U(i,1)*solver%Y(i,1)) / solver%V(i,1)
110  END IF check_inner_boundary
111  check_outer_boundary: IF (solver%V(i,2).NE.0.0_r8) THEN
112  solver%DY(i,solver%NRHO) = (solver%W(i,2) - solver%U(i,2)*solver%Y(i,solver%NRHO)) / solver%V(i,2)
113  END IF check_outer_boundary
114 
115  END IF derivative_recalculate
116 
117  END DO check_derivative
118 
119 
120 ! CHECK errors on solution and its derivative:
121 
122  IF (debug) THEN
123  i = solver%NRHO/2
124  WRITE(*,*) 'Solution maximum fractional error (mid radius) = ', &
125  maxval(abs( &
126  solver%c(1:solver%ndim,:)*solver%a(1:solver%ndim,:)*solver%y(1:solver%ndim,:) &
127  - solver%c(1:solver%ndim,:)*solver%b(1:solver%ndim,:)*solver%ym(1:solver%ndim,:) &
128  - solver%h*solver%d(1:solver%ndim,:)*solver%dy(1:solver%ndim,:) &
129  + solver%h*solver%e(1:solver%ndim,:)*solver%y(1:solver%ndim,:) &
130  - solver%h*solver%c(1:solver%ndim,:)*solver%f(1:solver%ndim,:) &
131  + solver%h*solver%c(1:solver%ndim,:)*solver%g(1:solver%ndim,:)*solver%y(1:solver%ndim,:) )) &
132  / &
133  max( tiny(1.0_r8), &
134  maxval(abs( solver%c(1:solver%ndim,:)*solver%a(1:solver%ndim,:)*solver%y(1:solver%ndim,:) )), &
135  maxval(abs( solver%c(1:solver%ndim,:)*solver%b(1:solver%ndim,:)*solver%ym(1:solver%ndim,:) )), &
136  maxval(abs( solver%h*solver%d(1:solver%ndim,:)*solver%dy(1:solver%ndim,:) )), &
137  maxval(abs( solver%h*solver%e(1:solver%ndim,:)*solver%y(1:solver%ndim,:) )), &
138  maxval(abs( solver%h*solver%c(1:solver%ndim,:)*solver%f(1:solver%ndim,:) )), &
139  maxval(abs( solver%h*solver%c(1:solver%ndim,:)*solver%g(1:solver%ndim,:)*solver%y(1:solver%ndim,:) )) &
140  )
141 
142 
143  WRITE(*,*) 'Solution maximum fractional error (Boundary 1) = ', &
144  maxval(abs( &
145  solver%v(1:solver%ndim,1)*solver%dy(1:solver%ndim,1) &
146  + solver%u(1:solver%ndim,1)*solver%y(1:solver%ndim,1) &
147  - solver%w(1:solver%ndim,1))) &
148  / &
149  max( tiny(1.0_r8), &
150  maxval(abs( solver%v(1:solver%ndim,1)*solver%dy(1:solver%ndim,1) )), &
151  maxval(abs( solver%u(1:solver%ndim,1)*solver%y(1:solver%ndim,1) )), &
152  maxval(abs( solver%w(1:solver%ndim,1) )))
153 
154 
155  WRITE(*,*) 'Solution maximum fractional error (Boundary 2) = ', &
156  maxval(abs( &
157  solver%v(1:solver%ndim,2)*solver%dy(1:solver%ndim,solver%nrho) &
158  + solver%u(1:solver%ndim,2)*solver%y(1:solver%ndim,solver%nrho) &
159  - solver%w(1:solver%ndim,2))) &
160  / &
161  max( tiny(1.0_r8), &
162  maxval(abs( solver%v(1:solver%ndim,2)*solver%dy(1:solver%ndim,solver%nrho) )), &
163  maxval(abs( solver%u(1:solver%ndim,2)*solver%y(1:solver%ndim,solver%nrho) )), &
164  maxval(abs( solver%w(1:solver%ndim,2) )))
165 
166  END IF
167 
168  RETURN
169 
170  END SUBROUTINE solution_interface
171 
172 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
173 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
174 
175 
176 
177 
subroutine solution6(solver, ifail)
Definition: solution6.f90:55
subroutine solution_interface(SOLVER, ifail)
INTERFACE TO NUMERICAL SOLVER.
Definition: solver.f90:1
subroutine fun(X, F)
Definition: Ev2.f:10
subroutine solution1(SOLVER, ifail)
This subroutine is prepared to solve single transport equation in standardised form adopted by the ET...
Definition: solution1.f90:9
subroutine solution3(SOLVER, ifail)
This subroutine solves transport equations using matrix PROGONKA method.
Definition: solution3.f90:8
subroutine deriv_fun(N, X, Y, DY)
Definition: ets_math.f90:19
subroutine solution10(SOLVER, ifail)
This subroutine is prepared to solve single transport equation in standardised form adopted by the ET...
Definition: solution10.F90:9
subroutine solutionfem(SOLVER, ifail)
This subroutine is prepared to solve single transport equation in standardised form adopted by the ET...
Definition: SOLVERFEM.f90:11
subroutine solution4(SOLVER, ifail)
This subroutine solves transport equations using matrix PROGONKA method.
Definition: solution4.f90:8
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
subroutine solution7(SOLVER, ifail)
This subroutine is prepared to solve single transport equation in standardised form adopted by the ET...
Definition: solution7.f90:12
subroutine solution2(SOLVER, ifail)
NUMERICAL SOLUTION.
Definition: solution2.f90:13