ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
convergence_check.f90
Go to the documentation of this file.
1 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
7 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
9 
10 CONTAINS
11 
12 
13 
14 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
21 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
22  SUBROUTINE check_convergence (COREPROF_ITER, COREPROF_NEW, CONTROL_DOUBLE)
23 
24 !-------------------------------------------------------!
25 ! This routinechecks the convergence of plasma !
26 ! profiles. !
27 !-------------------------------------------------------!
28 ! Source: --- !
29 ! Developers: D.Kalupin !
30 ! Kontacts: D.Kalupin@fz-juelich.de !
31 ! !
32 ! Comments: --- !
33 ! !
34 !-------------------------------------------------------!
35 
36 
37 ! +++ Declaration of variables:
38  USE euitm_schemas
39  USE copy_structures
40  USE ets_plasma
41  USE copy_cpo_ets
42 
43 
44  IMPLICIT NONE
45 
46 ! +++ CPO derived types:
47  TYPE (type_coreprof), POINTER :: coreprof_iter(:) !input/output CPO with internal ETS parameters profiles
48  TYPE (type_coreprof), POINTER :: coreprof_new(:) !input/output CPO with internal ETS parameters profiles
49 
50 
51 ! +++ Internal ETS derived types:
52  REAL (R8) :: control_double(5)!real control parameters
53  REAL (R8) :: conv
54 
55 ! +++ local
56 
57  REAL (R8) :: err_psi, err_ni, err_te, err_ti, err_vtor
58  REAL (R8), PARAMETER :: psi_0 = 1.0e-3_r8
59  REAL (R8), PARAMETER :: ni_0 = 1.0e10_r8
60  REAL (R8), PARAMETER :: te_0 = 1.0e-3_r8
61  REAL (R8), PARAMETER :: ti_0 = 1.0e-3_r8
62  REAL (R8), PARAMETER :: vtor_0 = 1.0e-3_r8
63 
64 ! +++ Check convergence:
65 
66  err_psi = maxval(abs(1.0_r8 - (abs(coreprof_iter(1)%psi%value)+psi_0)/(abs(coreprof_new(1)%psi%value)+psi_0)))
67  err_ni = maxval(abs(1.0_r8 - (abs(coreprof_iter(1)%ni%value)+ni_0)/(abs(coreprof_new(1)%ni%value)+ni_0)))
68  err_te = maxval(abs(1.0_r8 - (abs(coreprof_iter(1)%te%value)+te_0)/(abs(coreprof_new(1)%te%value)+te_0)))
69  err_ti = maxval(abs(1.0_r8 - (abs(coreprof_iter(1)%ti%value)+ti_0)/(abs(coreprof_new(1)%ti%value)+ti_0)))
70  err_vtor = maxval(abs(1.0_r8 - (abs(coreprof_iter(1)%vtor%value)+vtor_0)/(abs(coreprof_new(1)%vtor%value)+vtor_0)))
71 
72  !write(*,*) ' psi err ', err_psi
73  !write(*,*) ' ni err ', err_ni
74  !write(*,*) ' te err ', err_te
75  !write(*,*) ' ti err ', err_ti
76  !write(*,*) 'vtor err ', err_vtor
77 
78  conv = max(err_psi, err_ni, err_te, err_ti, err_vtor)
79 
80  control_double(4) = conv
81 
82  RETURN
83 
84 
85 
86  END SUBROUTINE check_convergence
87 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
88 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
89 
90 
91 
92 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
102 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
103  SUBROUTINE check_convergence_neutrals (CORENEUTRALS_ITER, CORENEUTRALS_NEW, CONV)
104 
105 !-------------------------------------------------------!
106 ! This routinechecks the convergence of plasma !
107 ! profiles. !
108 !-------------------------------------------------------!
109 ! Source: --- !
110 ! Developers: D. Coster !
111 ! Kontacts: David.Coster@ipp.mpg.de !
112 ! !
113 ! Comments: --- !
114 ! !
115 !-------------------------------------------------------!
116 
117 
118 ! +++ Declaration of variables:
119  USE euitm_schemas
120  USE copy_structures
121  USE ets_plasma
122  USE copy_cpo_ets
123 
124 
125  IMPLICIT NONE
126 
127  INTEGER :: ineut, itype
128 
129 ! +++ CPO derived types:
130  TYPE (type_coreneutrals), POINTER :: coreneutrals_iter(:) !input/output CPO with internal ETS parameters profiles
131  TYPE (type_coreneutrals), POINTER :: coreneutrals_new(:) !input/output CPO with internal ETS parameters profiles
132 
133 
134 ! +++ Internal ETS derived types:
135  REAL (R8) :: conv
136 
137 ! +++ local
138 
139  REAL (R8) :: err_neut
140  REAL (R8), PARAMETER :: ni_0 = 1.0e10_r8
141 
142 ! +++ Check convergence:
143 
144  err_neut = 0.0
145 
146  do ineut = 1, size(coreneutrals_iter(1)%PROFILES)
147  do itype = 1, size(coreneutrals_iter(1)%PROFILES(ineut)%NEUTRALTYPE)
148  err_neut = max(err_neut, &
149  maxval(abs(1.0_r8 - (abs(coreneutrals_iter(1)%PROFILES(ineut)%NEUTRALTYPE(itype)%n0%value)+ni_0)/ &
150  (abs(coreneutrals_new(1)%PROFILES(ineut)%NEUTRALTYPE(itype)%n0%value)+ni_0))))
151  enddo
152  enddo
153 
154  !write(*,*) ' n0 err ', err_neut
155 
156  conv = err_neut
157 
158  RETURN
159 
160 
161 
162  END SUBROUTINE check_convergence_neutrals
163 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
164 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
165 
166 
167 
168 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
175 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
176  SUBROUTINE check_convergence_impurities (COREIMPUR_ITER, COREIMPUR_NEW, CONV)
177 
178 !-------------------------------------------------------!
179 ! This routinechecks the convergence of plasma !
180 ! profiles. !
181 !-------------------------------------------------------!
182 ! Source: --- !
183 ! Developers: D. Coster !
184 ! Kontacts: David.Coster@ipp.mpg.de !
185 ! !
186 ! Comments: --- !
187 ! !
188 !-------------------------------------------------------!
189 
190 
191 ! +++ Declaration of variables:
192  USE euitm_schemas
193  USE copy_structures
194  USE ets_plasma
195  USE copy_cpo_ets
196 
197 
198  IMPLICIT NONE
199 
200  INTEGER :: iimp
201 
202 ! +++ CPO derived types:
203  TYPE (type_coreimpur), POINTER :: coreimpur_iter(:) !input/output CPO with internal ETS parameters profiles
204  TYPE (type_coreimpur), POINTER :: coreimpur_new(:) !input/output CPO with internal ETS parameters profiles
205 
206 
207 ! +++ Internal ETS derived types:
208  REAL (R8) :: control_double(5)!real control parameters
209  REAL (R8) :: conv
210 
211 ! +++ local
212 
213  REAL (R8) :: err_imp
214  REAL (R8), PARAMETER :: nz_0 = 1.0e10_r8
215 
216 ! +++ Check convergence:
217 
218  err_imp = 0.0_r8
219 
220  do iimp = 1, size(coreimpur_iter(1)%IMPURITY)
221  err_imp = max(err_imp, &
222  maxval(abs(1.0_r8 - (abs(coreimpur_iter(1)%IMPURITY(iimp)%NZ(:,:))+nz_0)/ &
223  (abs(coreimpur_new(1)%IMPURITY(iimp)%NZ(:,:))+nz_0))))
224 
225 
226  enddo
227 
228  !write(*,*) 'nimp err ', err_imp
229 
230  conv = err_imp
231 
232  RETURN
233 
234 
235 
236  END SUBROUTINE check_convergence_impurities
237 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
238 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
239 
240 
241 
242 END MODULE convergence_check
subroutine check_convergence_neutrals(CORENEUTRALS_ITER, CORENEUTRALS_NEW, CONV)
Convergence check neutrals This routine checks the convergence of plasma profiles.
Module provides routines for copying parts of CPOs (COREPROF and EQUILIBRIUM)
Definition: copy_cpo_ets.f90:8
subroutine check_convergence(COREPROF_ITER, COREPROF_NEW, CONTROL_DOUBLE)
Convergence check This routine checks the convergence of plasma profiles.
The module declares types of variables used in ETS (transport code)
Definition: ets_plasma.f90:8
subroutine check_convergence_impurities(COREIMPUR_ITER, COREIMPUR_NEW, CONV)
Convergence check impurities This routine checks the convergence of plasma profiles.
Module provides the convergence check for the ETS.