ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
convert.f90
Go to the documentation of this file.
1 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
7 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
8 MODULE convert
9 
10  IMPLICIT NONE
11 
12 CONTAINS
14  (equilibrium_old, equilibrium_iter, coreprof_old, coreprof_iter, &
15  coretransp, coresource, coreimpur, corefast, &
16  control_integer, control_double, &
17 !
18  geometry, profiles, transport, sources, impurity, evolution, &
19  control, j_boun, diag)
20 
21 
22 !-------------------------------------------------------!
23 ! This routine converts CPOs into the ETS !
24 ! derived types. !
25 !-------------------------------------------------------!
26 ! Source: --- !
27 ! Developers: D.Kalupin !
28 ! Kontacts: D.Kalupin@fz-juelich.de !
29 ! !
30 ! Comments: --- !
31 ! !
32 !-------------------------------------------------------!
33 
34 
35  USE itm_types
36  USE itm_constants
37  USE euitm_schemas
38 
39  USE ets_plasma
41  USE interpolate_cpo
42  USE copy_structures
43  USE deallocate_structures
44 
45  IMPLICIT NONE
46 
47 
48 ! +++ CPO derived types:
49  TYPE (type_equilibrium), POINTER :: equilibrium_old(:) !input CPO with geometry
50  TYPE (type_equilibrium), POINTER :: equilibrium_iter(:) !input CPO with geometry
51  TYPE (type_coreprof), POINTER :: coreprof_old(:) !input CPO with plasma profiles
52  TYPE (type_coreprof), POINTER :: coreprof_iter(:) !input CPO with plasma profiles
53  TYPE (type_coretransp), POINTER :: coretransp(:) !input CPO with transport coefficients
54  TYPE (type_coresource), POINTER :: coresource(:) !input CPO with sources
55  TYPE (type_coreimpur), POINTER :: coreimpur(:) !input CPO with impurity profiles
56  TYPE (type_corefast), POINTER :: corefast(:) !input CPO with none thermal profiles
57  TYPE (type_coreimpur), POINTER :: coreimpur_int(:) !input CPO with impurity profiles
58  INTEGER, INTENT(IN) :: control_integer(4) !integer control parameters
59  REAL (R8), INTENT(IN) :: control_double(6) !real control parameters
60 
61 ! +++ ETS derived types:
62  TYPE (magnetic_geometry), INTENT(INOUT) :: geometry !contains all geometry quantities
63  TYPE (plasma_profiles), INTENT(INOUT) :: profiles !contains profiles of plasma parameters
64  TYPE (transport_coefficients), INTENT(INOUT) :: transport !contains profiles of trasport coefficients
65  TYPE (sources_and_sinks), INTENT(INOUT) :: sources !contains profiles of sources
66  TYPE (impurity_profiles), INTENT(INOUT) :: impurity !contains profiles of impurities
67  TYPE (time_evolution), INTENT(INOUT) :: evolution !contains all parameters required by time evolution
68  TYPE (run_control), INTENT(INOUT) :: control !contains all parameters required by run
69  TYPE (diagnostic), INTENT(INOUT) :: diag !contains warnings and error messages
70 
71 
72 ! +++ Dimensions & indexes:
73  INTEGER :: neq, neq_old
74  INTEGER :: nrho, irho
75  INTEGER :: nrho_old
76  INTEGER :: nrho_tr
77  INTEGER :: nrho_src
78  INTEGER :: nrho_imp
79  INTEGER :: nrho_fast
80  INTEGER :: nnucl, inucl
81  INTEGER :: nion, iion, ifl
82  INTEGER :: nimp, iimp
83  INTEGER :: nnucl_fast, inucl_fast
84  INTEGER :: nimp_fast, iimp_fast
85  INTEGER :: nion_fast, iion_fast
86  INTEGER, ALLOCATABLE :: nzimp(:)
87  INTEGER :: izimp
88  INTEGER :: nneut
89  INTEGER, ALLOCATABLE :: ncomp(:)
90  INTEGER, ALLOCATABLE :: ntype(:)
91  INTEGER, ALLOCATABLE :: nzimp_fast(:)
92  INTEGER :: izimp_fast
93  INTEGER :: nneut_fast
94  INTEGER, ALLOCATABLE :: ncomp_fast(:)
95  INTEGER, ALLOCATABLE :: ntype_fast(:)
96  INTEGER :: nvalues_fast, ival
97  integer :: j_boun
98 
99 ! +++ Local variables:
100  REAL (R8) :: vol_eq, err_eq, vol_c, err_c, vol2_eq, vol2_c
101 
102  REAL (R8), ALLOCATABLE :: fun1(:),fun2(:)
103  REAL (R8), ALLOCATABLE :: rho_norm_old(:)
104  REAL (R8), ALLOCATABLE :: rho_norm_eq(:)
105  REAL (R8), ALLOCATABLE :: rho_norm_eq_old(:)
106  REAL (R8), ALLOCATABLE :: rho_norm_fast(:)
107  REAL (R8), ALLOCATABLE :: rho_norm_transp(:)
108  REAL (R8), ALLOCATABLE :: rho_norm_src(:)
109 
110 
111 
112 ! +++ Dimensions & Grid:
113  neq = SIZE(equilibrium_iter(1)%profiles_1d%psi)
114  neq_old = SIZE(equilibrium_old(1)%profiles_1d%psi)
115  nrho = SIZE(coreprof_iter(1)%rho_tor)
116  nrho_old = SIZE(coreprof_old(1)%rho_tor)
117 
118  ALLOCATE (rho_norm_old(nrho_old))
119  ALLOCATE (rho_norm_eq(neq))
120  ALLOCATE (rho_norm_eq_old(neq_old))
121 
122  IF(ASSOCIATED(coreprof_iter(1)%rho_tor_norm).AND.coreprof_iter(1)%rho_tor_norm(nrho).EQ.1.0_r8) THEN
123  geometry%RHO_NORM = coreprof_iter(1)%rho_tor_norm
124  ELSE
125  geometry%RHO_NORM = coreprof_iter(1)%rho_tor/coreprof_iter(1)%rho_tor(nrho)
126  END IF
127 
128  geometry%RHO = geometry%RHO_NORM * equilibrium_iter(1)%profiles_1d%rho_tor(neq)
129 
130  rho_norm_old = coreprof_old(1)%rho_tor/coreprof_old(1)%rho_tor(nrho_old)
131  rho_norm_eq = equilibrium_iter(1)%profiles_1d%rho_tor/equilibrium_iter(1)%profiles_1d%rho_tor(neq)
132  rho_norm_eq_old = equilibrium_old(1)%profiles_1d%rho_tor/equilibrium_old(1)%profiles_1d%rho_tor(neq_old)
133 
134 
135  CALL get_comp_dimensions(coreprof_iter(1)%COMPOSITIONS, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp)
136 
137 
138 ! +++ Convert geometry:
139 !dy GEOMETRY%RHO = COREPROF_ITER(1)%rho_tor
140  geometry%R0 = equilibrium_iter(1)%global_param%toroid_field%r0
141  geometry%B0 = equilibrium_iter(1)%global_param%toroid_field%b0
142  geometry%RGEO = equilibrium_iter(1)%eqgeometry%geom_axis%r
143  geometry%BGEO = geometry%B0*geometry%R0/geometry%RGEO
144 
145  geometry%PHI_BND = equilibrium_iter(1)%profiles_1d%phi(neq)
146  geometry%RHO_BND = equilibrium_iter(1)%profiles_1d%rho_tor(neq)
147  IF (equilibrium_iter(1)%time.GT.equilibrium_old(1)%time) THEN
148  geometry%PHI_BND_PRIME= (equilibrium_iter(1)%profiles_1d%phi(neq)-equilibrium_old(1)%profiles_1d%phi(neq_old))&
149  /(equilibrium_iter(1)%time-equilibrium_old(1)%time)
150  geometry%RHO_BND_PRIME= (equilibrium_iter(1)%profiles_1d%rho_tor(neq)-equilibrium_old(1)%profiles_1d%rho_tor(neq_old))&
151  /(equilibrium_iter(1)%time-equilibrium_old(1)%time)
152  END IF
153 
154  evolution%BTM = equilibrium_old(1)%global_param%toroid_field%b0 * &
155  equilibrium_old(1)%global_param%toroid_field%r0/equilibrium_old(1)%eqgeometry%geom_axis%r
156 
157 
158  CALL l3deriv(equilibrium_iter(1)%profiles_1d%volume, rho_norm_eq, neq, &
159  geometry%VPR, geometry%RHO_NORM, nrho)
160  geometry%VPR = geometry%VPR / equilibrium_iter(1)%profiles_1d%rho_tor(neq)
161  CALL l3deriv(equilibrium_old(1)%profiles_1d%volume, rho_norm_eq_old, neq_old, &
162  geometry%VPRM, geometry%RHO_NORM, nrho)
163  geometry%VPRM = geometry%VPRM / equilibrium_old(1)%profiles_1d%rho_tor(neq_old)
164  CALL l3interp(equilibrium_iter(1)%profiles_1d%gm3, rho_norm_eq, neq, &
165  geometry%G1, geometry%RHO_NORM, nrho)
166  CALL l3interp(equilibrium_iter(1)%profiles_1d%gm8, rho_norm_eq, neq, &
167  geometry%G2, geometry%RHO_NORM, nrho)
168  CALL l3interp(equilibrium_old(1)%profiles_1d%gm8, rho_norm_eq_old, neq_old, &
169  geometry%G2M, geometry%RHO_NORM, nrho)
170  CALL l3interp(equilibrium_iter(1)%profiles_1d%gm2, rho_norm_eq, neq, &
171  geometry%G3, geometry%RHO_NORM, nrho)
172  CALL l3interp(equilibrium_iter(1)%profiles_1d%F_dia, rho_norm_eq, neq, &
173  geometry%FDIA, geometry%RHO_NORM, nrho)
174 
175  IF (geometry%VPR(1).LE.0._r8) geometry%VPR(1) = 0._r8
176  IF (geometry%VPRM(1).LE.0._r8) geometry%VPRM(1) = 0._r8
177 
178 
179 
180 
181 
182 ! +++ Convert profiles:
183  DO iion =1, nion
184  profiles%ZION(iion) = coreprof_iter(1)%compositions%ions(iion)%zion
185  profiles%ZION2(iion) = coreprof_iter(1)%compositions%ions(iion)%zion**2
186  profiles%MION(iion) = coreprof_iter(1)%compositions%nuclei(coreprof_iter(1)%compositions%ions(iion)%nucindex)%amn
187  END DO
188 
189  profiles%PSI = coreprof_iter(1)%psi%value
190  profiles%DPSI = coreprof_iter(1)%psi%ddrho
191 !dy begin check for q profile if current diffusion eq is OFF and replace it with
192 ! q profile from equilibrium
193  if ((coreprof_iter(1)%psi%boundary%type.eq.0).and.(all((abs(coreprof_iter(1)%profiles1d%q%value)).lt.1.0e-6))) then
194  write(*,*) 'WARNING,interpretative mode is chosen for current diffusion equation'
195  write(*,*) 'but no q profile is supplied (primary quantity)'
196  write(*,*) 'replace it with q profile from equilibrium'
197  CALL l3interp(equilibrium_iter(1)%profiles_1d%q, rho_norm_eq, neq, &
198  profiles%QSF, geometry%RHO_NORM, nrho)
199  else
200  profiles%QSF = coreprof_iter(1)%profiles1d%q%value
201  end if
202  profiles%PSI_BND = coreprof_iter(1)%psi%boundary%value
203  profiles%PSI_BND_TYPE = coreprof_iter(1)%psi%boundary%type
204  profiles%CURR_PAR = coreprof_iter(1)%profiles1d%jtot%value
205  profiles%CURR_TOR = coreprof_iter(1)%profiles1d%jphi%value
206 
207  profiles%NI = coreprof_iter(1)%ni%value
208  profiles%DNI = coreprof_iter(1)%ni%ddrho
209  profiles%NI_BND = coreprof_iter(1)%ni%boundary%value
210  profiles%NI_BND_TYPE = coreprof_iter(1)%ni%boundary%type
211  profiles%NI_BND_RHO = coreprof_iter(1)%ni%boundary%rho_tor
212 
213  profiles%NE = coreprof_iter(1)%ne%value
214  profiles%DNE = coreprof_iter(1)%ne%ddrho
215  profiles%NE_BND = coreprof_iter(1)%ne%boundary%value
216  profiles%NE_BND_TYPE = coreprof_iter(1)%ne%boundary%type
217  profiles%NE_BND_RHO = coreprof_iter(1)%ne%boundary%rho_tor
218 
219  profiles%ZEFF = coreprof_iter(1)%profiles1d%zeff%value
220 
221  profiles%TI = coreprof_iter(1)%ti%value
222  profiles%DTI = coreprof_iter(1)%ti%ddrho
223  profiles%TI_BND = coreprof_iter(1)%ti%boundary%value
224  profiles%TI_BND_TYPE = coreprof_iter(1)%ti%boundary%type
225  profiles%TI_BND_RHO = coreprof_iter(1)%ti%boundary%rho_tor
226 
227  profiles%TE = coreprof_iter(1)%te%value
228  profiles%DTE = coreprof_iter(1)%te%ddrho
229  profiles%TE_BND = coreprof_iter(1)%te%boundary%value
230  profiles%TE_BND_TYPE = coreprof_iter(1)%te%boundary%type
231  profiles%TE_BND_RHO = coreprof_iter(1)%te%boundary%rho_tor
232 
233  profiles%WTOR = coreprof_iter(1)%profiles1d%wtor%value
234  profiles%VTOR = coreprof_iter(1)%vtor%value
235  profiles%DVTOR = coreprof_iter(1)%vtor%ddrho
236  profiles%VTOR_BND = coreprof_iter(1)%vtor%boundary%value
237  profiles%VTOR_BND_TYPE = coreprof_iter(1)%vtor%boundary%type
238  profiles%VTOR_BND_RHO = coreprof_iter(1)%vtor%boundary%rho_tor
239 
240  profiles%ZEFF = coreprof_iter(1)%profiles1d%zeff%value
241 
242 
243 
244 ! +++ Profiles at previous time step:
245 !dy CALL L3deriv (EQUILIBRIUM_OLD(1)%profiles_1d%volume, EQUILIBRIUM_OLD(1)%profiles_1d%rho_tor, NEQ_OLD, &
246 !dy EVOLUTION%VPRM, GEOMETRY%RHO, NRHO)
247  evolution%VPRM=geometry%VPRM
248  CALL l3interp(equilibrium_old(1)%profiles_1d%gm8, rho_norm_eq_old, nrho_old, &
249  evolution%G2M, geometry%RHO_NORM, nrho)
250  CALL l3interp(coreprof_old(1)%psi%value, rho_norm_old, nrho_old, &
251  evolution%PSIM, geometry%RHO_NORM, nrho)
252  CALL l3interp(coreprof_old(1)%psi%ddrho, rho_norm_old, nrho_old, &
253  evolution%DPSIM, geometry%RHO_NORM, nrho)
254  CALL l3interp(coreprof_old(1)%ne%value, rho_norm_old, nrho_old, &
255  evolution%NEM, geometry%RHO_NORM, nrho)
256  CALL l3interp(coreprof_old(1)%ne%ddrho, rho_norm_old, nrho_old, &
257  evolution%DNEM, geometry%RHO_NORM, nrho)
258  CALL l3interp(coreprof_old(1)%te%value, rho_norm_old, nrho_old, &
259  evolution%TEM, geometry%RHO_NORM, nrho)
260  CALL l3interp(coreprof_old(1)%te%ddrho, rho_norm_old, nrho_old, &
261  evolution%DTEM, geometry%RHO_NORM, nrho)
262  DO iion = 1, nion
263  IF(iion.LE.SIZE(coreprof_old(1)%ni%value, dim=2)) &
264  CALL l3interp(coreprof_old(1)%ni%value(:,iion), rho_norm_old, nrho_old, &
265  evolution%NIM(:,iion), geometry%RHO_NORM, nrho)
266  CALL l3interp(coreprof_old(1)%ni%ddrho(:,iion), rho_norm_old, nrho_old, &
267  evolution%DNIM(:,iion), geometry%RHO_NORM, nrho)
268  IF(iion.LE.SIZE(coreprof_old(1)%ti%value, dim=2)) &
269  CALL l3interp(coreprof_old(1)%ti%value(:,iion), rho_norm_old, nrho_old, &
270  evolution%TIM(:,iion), geometry%RHO_NORM, nrho)
271  CALL l3interp(coreprof_old(1)%ti%ddrho(:,iion), rho_norm_old, nrho_old, &
272  evolution%DTIM(:,iion), geometry%RHO_NORM, nrho)
273  IF(iion.LE.SIZE(coreprof_old(1)%vtor%value, dim=2)) &
274  CALL l3interp(coreprof_old(1)%vtor%value(:,iion), rho_norm_old, nrho_old, &
275  evolution%VTORM(:,iion), geometry%RHO_NORM, nrho)
276  CALL l3interp(coreprof_old(1)%vtor%ddrho(:,iion), rho_norm_old, nrho_old, &
277  evolution%DVTORM(:,iion), geometry%RHO_NORM, nrho)
278  END DO
279 
280  IF (evolution%VPRM(1).LE.0._r8) evolution%VPRM(1) = 0._r8
281 
282 ! +++ Convert fast particles:
283 !
284  IF(ALLOCATED(fun1)) DEALLOCATE (fun1)
285  ALLOCATE(fun1(nrho))
286 
287  IF (ASSOCIATED(corefast)) THEN
288  CALL get_comp_dimensions(corefast(1)%COMPOSITIONS, nnucl_fast, nion_fast, nimp_fast, nzimp_fast, nneut_fast, ntype_fast, ncomp_fast)
289  IF (ASSOCIATED(corefast(1)%VALUES)) THEN
290  nvalues_fast = SIZE(corefast(1)%VALUES)
291  loop_on_values: DO ival=1, nvalues_fast
292  IF (ASSOCIATED(corefast(1)%VALUES(ival)%rho_tor)) THEN
293  nrho_fast = SIZE(corefast(1)%VALUES(ival)%rho_tor)
294  IF(ALLOCATED(rho_norm_fast)) DEALLOCATE (rho_norm_fast)
295  ALLOCATE (rho_norm_fast(nrho_fast))
296  rho_norm_fast = corefast(1)%VALUES(ival)%rho_tor/corefast(1)%VALUES(ival)%rho_tor(nrho_fast)
297  ! electrons
298  IF(ASSOCIATED(corefast(1)%VALUES(ival)%ne)) THEN
299  CALL l3interp(corefast(1)%VALUES(ival)%ne, rho_norm_fast, nrho_fast, &
300  fun1, geometry%RHO_NORM, nrho)
301  profiles%NE_FAST = profiles%NE_FAST + fun1
302  ENDIF
303  IF(ASSOCIATED(corefast(1)%VALUES(ival)%pe)) THEN
304  CALL l3interp(corefast(1)%VALUES(ival)%pe, rho_norm_fast, nrho_fast, &
305  fun1, geometry%RHO_NORM, nrho)
306  profiles%PE_FAST = profiles%PE_FAST + fun1
307  ENDIF
308  ! ions
309  thermal_ions_loop: DO iion = 1, nion
310  inucl = coreprof_iter(1)%COMPOSITIONS%IONS(iion)%nucindex
311  fast_ions_loop: DO iion_fast = 1, nion_fast
312  inucl_fast = corefast(1)%COMPOSITIONS%IONS(iion_fast)%nucindex
313  IF (.not. (inucl_fast.LE.0 .OR. inucl_fast.GT.SIZE(corefast(1)%COMPOSITIONS%NUCLEI))) THEN
314  check_for_ions_consistency: IF &
315  (abs(coreprof_iter(1)%COMPOSITIONS%NUCLEI(inucl)%amn - corefast(1)%COMPOSITIONS%NUCLEI(inucl_fast)%amn) .LE. 0.25 .AND. &
316  abs(coreprof_iter(1)%COMPOSITIONS%NUCLEI(inucl)%zn - corefast(1)%COMPOSITIONS%NUCLEI(inucl_fast)%zn ) .LE. 0.25 .AND. &
317  abs(coreprof_iter(1)%COMPOSITIONS%IONS(iion)%zion - corefast(1)%COMPOSITIONS%IONS(iion_fast)%zion ) .LE. 0.25) THEN
318  ! Ni
319  IF(ASSOCIATED(corefast(1)%VALUES(ival)%ni)) THEN
320  CALL l3interp(corefast(1)%VALUES(ival)%ni(:,iion_fast), rho_norm_fast, nrho_fast, &
321  fun1, geometry%RHO_NORM, nrho)
322  profiles%NI_FAST(:,iion) = profiles%NI_FAST(:,iion) + fun1(:)
323  ENDIF
324  ! Pi
325  IF(ASSOCIATED(corefast(1)%VALUES(ival)%pi)) THEN
326  CALL l3interp(corefast(1)%VALUES(ival)%pi(:,iion_fast), rho_norm_fast, nrho_fast, &
327  fun1, geometry%RHO_NORM, nrho)
328  profiles%PI_FAST(:, iion) = profiles%PI_FAST(:, iion) + fun1(:)
329  ENDIF
330 
331  ! Pi_para
332  ! left for later development
333 
334  ! Ui
335  ! left for later development
336 
337  END IF check_for_ions_consistency
338  ENDIF
339  END DO fast_ions_loop
340  END DO thermal_ions_loop
341  END IF
342  END DO loop_on_values
343  END IF
344  END IF
345 
346  IF(ALLOCATED(fun1)) DEALLOCATE (fun1)
347  IF(ALLOCATED(rho_norm_fast)) DEALLOCATE (rho_norm_fast)
348 ! +++ Convert transport:
349  nrho_tr = SIZE(coretransp(1)%VALUES(1)%rho_tor)
350  transport%C1(1) = 0.0e0_r8
351  transport%C1(2) = 1.5e0_r8
352  transport%C1(3) = 2.5e0_r8
353  transport%DIFF_NE = 0.0e0_r8
354  transport%VCONV_NE = 0.0e0_r8
355  transport%DIFF_NI = 0.0e0_r8
356  transport%VCONV_NI = 0.0e0_r8
357 
358  IF(ALLOCATED(rho_norm_transp)) DEALLOCATE (rho_norm_transp)
359  ALLOCATE (rho_norm_transp(nrho_tr))
360  rho_norm_transp = coretransp(1)%VALUES(1)%rho_tor/coretransp(1)%VALUES(1)%rho_tor(nrho_tr)
361 
362 
363 
364  CALL l3interp(coretransp(1)%VALUES(1)%sigma, rho_norm_transp, nrho_tr, &
365  transport%SIGMA, geometry%RHO_NORM, nrho)
366  DO ifl=1,3
367  CALL l3interp(coretransp(1)%VALUES(1)%ne_transp%diff_eff(:,ifl), rho_norm_transp, nrho_tr, &
368  transport%DIFF_NE(:,ifl), geometry%RHO_NORM, nrho)
369  CALL l3interp(coretransp(1)%VALUES(1)%ne_transp%vconv_eff(:,ifl), rho_norm_transp, nrho_tr, &
370  transport%VCONV_NE(:,ifl), geometry%RHO_NORM, nrho)
371  END DO
372  CALL l3interp(coretransp(1)%VALUES(1)%te_transp%diff_eff, rho_norm_transp, nrho_tr, &
373  transport%DIFF_TE, geometry%RHO_NORM, nrho)
374  CALL l3interp(coretransp(1)%VALUES(1)%te_transp%vconv_eff, rho_norm_transp, nrho_tr, &
375  transport%VCONV_TE, geometry%RHO_NORM, nrho)
376 
377  DO iion = 1, nion
378  DO ifl=1,3
379  CALL l3interp(coretransp(1)%VALUES(1)%ni_transp%diff_eff(:,iion,ifl), rho_norm_transp, nrho_tr, &
380  transport%DIFF_NI(:,iion,ifl), geometry%RHO_NORM, nrho)
381  CALL l3interp(coretransp(1)%VALUES(1)%ni_transp%vconv_eff(:,iion,ifl), rho_norm_transp, nrho_tr, &
382  transport%VCONV_NI(:,iion,ifl), geometry%RHO_NORM, nrho)
383  ENDDO
384  CALL l3interp(coretransp(1)%VALUES(1)%ti_transp%diff_eff(:,iion), rho_norm_transp, nrho_tr, &
385  transport%DIFF_TI(:,iion), geometry%RHO_NORM, nrho)
386  CALL l3interp(coretransp(1)%VALUES(1)%ti_transp%vconv_eff(:,iion), rho_norm_transp, nrho_tr, &
387  transport%VCONV_TI(:,iion), geometry%RHO_NORM, nrho)
388  CALL l3interp(coretransp(1)%VALUES(1)%vtor_transp%diff_eff(:,iion), rho_norm_transp, nrho_tr, &
389  transport%DIFF_VTOR(:,iion), geometry%RHO_NORM, nrho)
390  CALL l3interp(coretransp(1)%VALUES(1)%vtor_transp%vconv_eff(:,iion),rho_norm_transp, nrho_tr, &
391  transport%VCONV_VTOR(:,iion), geometry%RHO_NORM, nrho)
392  ENDDO
393  transport%QGI = 0.e0_r8
394  transport%QGE = sum(transport%QGI, dim=1)
395 
396 
397  IF(ALLOCATED(rho_norm_transp)) DEALLOCATE (rho_norm_transp)
398 
399 
400 ! +++ Convert sources:
401  nrho_src = SIZE(coresource(1)%VALUES(1)%rho_tor)
402  IF(.NOT.ASSOCIATED(coresource(1)%VALUES(1)%rho_tor_norm)) ALLOCATE (coresource(1)%VALUES(1)%rho_tor_norm(nrho_tr))
403  coresource(1)%VALUES(1)%rho_tor_norm = coresource(1)%VALUES(1)%rho_tor/coresource(1)%VALUES(1)%rho_tor(nrho_tr)
404  IF(ALLOCATED(rho_norm_src)) DEALLOCATE (rho_norm_src)
405  ALLOCATE (rho_norm_src(nrho_src))
406  rho_norm_src=coresource(1)%VALUES(1)%rho_tor_norm
407 
408  CALL l3interp(coresource(1)%VALUES(1)%sigma, rho_norm_src, nrho_src, &
409  sources%SIGMA, geometry%RHO_NORM, nrho)
410  CALL l3interp(coresource(1)%VALUES(1)%j, rho_norm_src, nrho_src, &
411  sources%CURR_EXP, geometry%RHO_NORM, nrho)
412  CALL l3interp(coresource(1)%VALUES(1)%qe%exp, rho_norm_src, nrho_src, &
413  sources%QE_EXP, geometry%RHO_NORM, nrho)
414  CALL l3interp(coresource(1)%VALUES(1)%qe%imp, rho_norm_src, nrho_src, &
415  sources%QE_IMP, geometry%RHO_NORM, nrho)
416  CALL l3interp(coresource(1)%VALUES(1)%se%exp, rho_norm_src, nrho_src, &
417  sources%SE_EXP, geometry%RHO_NORM, nrho)
418  CALL l3interp(coresource(1)%VALUES(1)%se%imp, rho_norm_src, nrho_src, &
419  sources%SE_IMP, geometry%RHO_NORM, nrho)
420 
421  DO iion = 1, nion
422  CALL l3interp(coresource(1)%VALUES(1)%si%exp(:,iion), rho_norm_src, nrho_src, &
423  sources%SI_EXP(:,iion), geometry%RHO_NORM, nrho)
424  CALL l3interp(coresource(1)%VALUES(1)%si%imp(:,iion), rho_norm_src, nrho_src, &
425  sources%SI_IMP(:,iion), geometry%RHO_NORM, nrho)
426  CALL l3interp(coresource(1)%VALUES(1)%qi%exp(:,iion), rho_norm_src, nrho_src, &
427  sources%QI_EXP(:,iion), geometry%RHO_NORM, nrho)
428  CALL l3interp(coresource(1)%VALUES(1)%qi%imp(:,iion), rho_norm_src, nrho_src, &
429  sources%QI_IMP(:,iion), geometry%RHO_NORM, nrho)
430  CALL l3interp(coresource(1)%VALUES(1)%ui%exp(:,iion), rho_norm_src, nrho_src, &
431  sources%UI_EXP(:,iion), geometry%RHO_NORM, nrho)
432  CALL l3interp(coresource(1)%VALUES(1)%ui%imp(:,iion), rho_norm_src, nrho_src, &
433  sources%UI_IMP(:,iion), geometry%RHO_NORM, nrho)
434  ENDDO
435  sources%CURR_IMP = 0.e0_r8 !not defined by the CORESOURCE CPO
436  sources%QE_EXP = sources%QE_EXP/itm_ev
437  sources%QI_EXP = sources%QI_EXP/itm_ev
438 
439  IF(ALLOCATED(rho_norm_src)) DEALLOCATE (rho_norm_src)
440 
441 ! +++ Convert impurities:
442  if(nimp .gt. 0) then
443  CALL allocate_coreimpur_cpo(1, nrho, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, coreimpur_int)
444  CALL copy_cpo(coreprof_iter(1)%COMPOSITIONS, coreimpur_int(1)%COMPOSITIONS)
445  coreimpur_int(1)%rho_tor = coreprof_iter(1)%rho_tor
446  coreimpur_int(1)%rho_tor_norm = coreprof_iter(1)%rho_tor_norm
447  CALL interpolate_impur_convert(coreimpur(1), coreimpur_int(1))
448 
449  DO iimp = 1, nimp
450  DO izimp = 1, nzimp(iimp)
451  impurity%NZ(:,iimp,izimp) = coreimpur_int(1)%impurity(iimp)%nz(:,izimp)
452  impurity%FLUX_NZ(:,iimp,izimp) = coreimpur_int(1)%impurity(iimp)%flux%flux_dv(:,izimp)
453  impurity%ZIMP(:,iimp,izimp) = coreimpur_int(1)%impurity(iimp)%z(:,izimp)
454  impurity%ZIMP2(:,iimp,izimp) = coreimpur_int(1)%impurity(iimp)%zsq(:,izimp)
455  END DO
456  ENDDO
457  CALL deallocate_cpo(coreimpur_int)
458  endif
459 
460 
461 ! +++ Convert control parameters:
462  control%SOLVER_TYPE = control_integer(1)
463  control%QUASI_NEUT = control_integer(3)
464  control%TAU = control_double(1)
465  control%AMIX = control_double(2)
466  control%AMIXTR = control_double(3)
467  control%CONV = control_double(4)
468  control%CONVREC = control_double(5)
469  control%OHMIC_HEATING_MULTIPLIER = control_double(6)
470  j_boun=control_integer(4)
471 
472 
473 
474  IF(ALLOCATED(nzimp)) DEALLOCATE (nzimp)
475  IF(ALLOCATED(ncomp)) DEALLOCATE (ncomp)
476  IF(ALLOCATED(ntype)) DEALLOCATE (ntype)
477  IF(ALLOCATED(fun1)) DEALLOCATE (fun1)
478  IF(ALLOCATED(fun2)) DEALLOCATE (fun2)
479  IF(ALLOCATED(rho_norm_old)) DEALLOCATE (rho_norm_old)
480  IF(ALLOCATED(rho_norm_eq)) DEALLOCATE (rho_norm_eq)
481  IF(ALLOCATED(rho_norm_eq_old)) DEALLOCATE (rho_norm_eq_old)
482 
483  RETURN
484 
485 
486  END SUBROUTINE convert_cpo_to_internal_types
487 
488 
489 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
490 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
491 
492 
493 
494 
495 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
501 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
502 
504  (geometry, profiles, transport, sources, global, coreprof, diag)
505 
506 !-------------------------------------------------------!
507 ! This routine converts ETS into the CPOs !
508 ! derived types. !
509 !-------------------------------------------------------!
510 ! Source: --- !
511 ! Developers: D.Kalupin !
512 ! Kontacts: D.Kalupin@fz-juelich.de !
513 ! !
514 ! Comments: --- !
515 ! !
516 !-------------------------------------------------------!
517 
518 
519  USE euitm_schemas
520  USE itm_constants
521 
522  USE ets_plasma
523 
524  IMPLICIT NONE
525 
526 ! +++ ETS derived types:
527  TYPE (magnetic_geometry), INTENT(IN) :: geometry !contains all geometry quantities
528  TYPE (plasma_profiles), INTENT(IN) :: profiles !contains profiles of plasma parameters
529  TYPE (transport_coefficients), INTENT(IN) :: transport !contains profiles of trasport coefficients
530  TYPE (sources_and_sinks), INTENT(IN) :: sources !contains profiles of sources
531  TYPE (global_param), INTENT(IN) :: global !contains global plasma parameters
532  TYPE (diagnostic), INTENT(IN) :: diag !contains error messages and warnings
533 
534 ! +++ CPO derived types:
535  TYPE (type_coreprof), POINTER :: coreprof(:)
536 
537 ! +++ COCOS:
538  coreprof(1)%datainfo%cocos = 13
539 
540 ! +++ Convert geometry:
541  coreprof(1)%rho_tor = geometry%RHO
542  coreprof(1)%rho_tor_norm = geometry%RHO_NORM
543  coreprof(1)%toroid_field%r0 = geometry%R0
544  coreprof(1)%toroid_field%b0 = geometry%B0
545 
546 
547 
548 ! +++ Convert profiles:
549  coreprof(1)%psi%value = profiles%PSI
550  coreprof(1)%psi%ddrho = profiles%DPSI !AF - 25.Sep.2014
551  coreprof(1)%psi%sigma_par%value = profiles%SIGMA
552  coreprof(1)%psi%boundary%value = profiles%PSI_BND
553  coreprof(1)%psi%boundary%type = profiles%PSI_BND_TYPE
554  coreprof(1)%psi%jni%value = profiles%JNI
555 
556 
557  coreprof(1)%ni%value = profiles%NI
558  coreprof(1)%ni%ddrho = profiles%DNI !AF - 25.Sep.2014
559  coreprof(1)%ni%flux%flux_dv = profiles%FLUX_NI
560  coreprof(1)%ni%boundary%value = profiles%NI_BND
561  coreprof(1)%ni%boundary%type = profiles%NI_BND_TYPE
562  coreprof(1)%ni%boundary%rho_tor = profiles%NI_BND_RHO
563  coreprof(1)%ni%transp_coef%diff = profiles%DIFF_NI
564  coreprof(1)%ni%transp_coef%vconv = profiles%VCONV_NI
565  coreprof(1)%ni%source_term%value = profiles%SOURCE_NI
566  coreprof(1)%ni%source_term%integral = profiles%INT_SOURCE_NI
567 
568  coreprof(1)%ne%value = profiles%NE
569  coreprof(1)%ne%ddrho = profiles%DNE !AF - 25.Sep.2014
570  coreprof(1)%ne%flux%flux_dv = profiles%FLUX_NE
571  coreprof(1)%ne%boundary%value = profiles%NE_BND
572  coreprof(1)%ne%boundary%type = profiles%NE_BND_TYPE
573  coreprof(1)%ne%boundary%rho_tor = profiles%NE_BND_RHO
574  coreprof(1)%ne%transp_coef%diff = profiles%DIFF_NE
575  coreprof(1)%ne%transp_coef%vconv = profiles%VCONV_NE
576  coreprof(1)%ne%source_term%value = profiles%SOURCE_NE
577  coreprof(1)%ne%source_term%integral = profiles%INT_SOURCE_NE
578 
579 
580  coreprof(1)%profiles1d%zeff%value = profiles%ZEFF
581 
582  coreprof(1)%ti%value = profiles%TI
583  coreprof(1)%ti%ddrho = profiles%DTI !AF - 25.Sep.2014
584  coreprof(1)%ti%flux%flux_dv = profiles%FLUX_TI*itm_ev
585  coreprof(1)%ti%boundary%value = profiles%TI_BND
586  coreprof(1)%ti%boundary%type = profiles%TI_BND_TYPE
587  coreprof(1)%ti%boundary%rho_tor = profiles%TI_BND_RHO
588  coreprof(1)%ti%transp_coef%diff = profiles%DIFF_TI
589  coreprof(1)%ti%transp_coef%vconv = profiles%VCONV_TI
590  coreprof(1)%ti%source_term%value = profiles%SOURCE_TI * itm_ev
591  coreprof(1)%ti%source_term%integral = profiles%INT_SOURCE_TI * itm_ev
592 
593  coreprof(1)%te%value = profiles%TE
594  coreprof(1)%te%ddrho = profiles%DTE !AF - 25.Sep.2014
595  coreprof(1)%te%flux%flux_dv = profiles%FLUX_TE*itm_ev
596  coreprof(1)%te%boundary%value = profiles%TE_BND
597  coreprof(1)%te%boundary%type = profiles%TE_BND_TYPE
598  coreprof(1)%te%boundary%rho_tor = profiles%TE_BND_RHO
599  coreprof(1)%te%transp_coef%diff = profiles%DIFF_TE
600  coreprof(1)%te%transp_coef%vconv = profiles%VCONV_TE
601  coreprof(1)%te%source_term%value = profiles%SOURCE_TE * itm_ev
602  coreprof(1)%te%source_term%integral = profiles%INT_SOURCE_TE * itm_ev
603 
604  coreprof(1)%profiles1d%wtor%value = profiles%WTOR
605  coreprof(1)%vtor%value = profiles%VTOR
606  coreprof(1)%vtor%ddrho = profiles%DVTOR !AF - 25.Sep.2014
607  coreprof(1)%vtor%flux%flux_dv = profiles%FLUX_MTOR
608  coreprof(1)%vtor%boundary%value = profiles%VTOR_BND
609  coreprof(1)%vtor%boundary%type = profiles%VTOR_BND_TYPE
610  coreprof(1)%vtor%boundary%rho_tor = profiles%VTOR_BND_RHO
611  coreprof(1)%vtor%transp_coef%diff = profiles%DIFF_VTOR
612  coreprof(1)%vtor%transp_coef%vconv = profiles%VCONV_VTOR
613  coreprof(1)%vtor%source_term%value = profiles%SOURCE_MTOR
614  coreprof(1)%vtor%source_term%integral = profiles%INT_SOURCE_MTOR
615 
616  coreprof(1)%profiles1d%jtot%value = profiles%CURR_PAR
617  coreprof(1)%profiles1d%jni%value = profiles%JNI
618  coreprof(1)%profiles1d%jphi%value = profiles%CURR_TOR
619  coreprof(1)%profiles1d%joh%value = profiles%JOH
620  coreprof(1)%profiles1d%vloop%value = profiles%VLOOP
621  coreprof(1)%profiles1d%sigmapar%value = profiles%SIGMA
622  coreprof(1)%profiles1d%qoh%value = profiles%QOH
623  coreprof(1)%profiles1d%qoh%integral = profiles%INT_QOH
624  coreprof(1)%profiles1d%eparallel%value = profiles%E_PAR
625  coreprof(1)%profiles1d%q%value = profiles%QSF
626  coreprof(1)%profiles1d%shear%value = profiles%SHEAR
627  coreprof(1)%profiles1d%bpol%value = profiles%BPOL
628  coreprof(1)%profiles1d%qei%value = profiles%QEI_OUT* itm_ev
629 
630  coreprof(1)%profiles1d%pe%value = profiles%TE * profiles%NE * itm_ev
631  coreprof(1)%profiles1d%pi%value = profiles%TI * profiles%NI * itm_ev
632  coreprof(1)%profiles1d%pi_tot%value = sum(coreprof(1)%profiles1d%pi%value, dim=2)
633  coreprof(1)%profiles1d%pr_th%value = coreprof(1)%profiles1d%pe%value + sum(coreprof(1)%profiles1d%pi%value, dim=2)
634  !COREPROF(1)%profiles1d%pr_perp%value = COREPROF(1)%profiles1d%pr_th%value
635  coreprof(1)%profiles1d%pr_perp%value = coreprof(1)%profiles1d%pr_th%value + sum(profiles%PI_FAST, dim=2)
636  coreprof(1)%profiles1d%pr_parallel%value = coreprof(1)%profiles1d%pr_th%value
637 
638 !+++CODEPARAM:
639  ALLOCATE (coreprof(1)%codeparam%codename(1))
640  ALLOCATE (coreprof(1)%codeparam%codeversion(1))
641  ALLOCATE (coreprof(1)%codeparam%output_diag(1))
642 
643  coreprof(1)%codeparam%codename = 'EU TRANSPORT SOLVER'
644  coreprof(1)%codeparam%codeversion = '01.01.2017'
645  coreprof(1)%codeparam%output_flag = diag%IERR
646  coreprof(1)%codeparam%output_diag(1) = "ETS: "//trim(adjustl(diag%ERROR_MESSAGE))
647 
648 ! +++ Convert global parameters:
649  coreprof(1)%globalparam%current_tot = global%CURRENT
650  coreprof(1)%globalparam%current_bnd = global%CURRENT
651  coreprof(1)%globalparam%current_ni = global%CURRENT_NI
652  coreprof(1)%globalparam%w_dia = global%WDIA
653 
654 
655 
656  RETURN
657 
658 
659  END SUBROUTINE convert_internal_to_cpo_types
660 
661 
662 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
663 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
664 
665 
666 
667 
668 
669 
670 
671 
672 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
673 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
674 !-------------------------------------------------------!
675 !-------------------------------------------------------!
676  SUBROUTINE convert_neoclassic2coretransp(NEOCLASSIC, CORETRANSP)
677 !-------------------------------------------------------!
678 ! This routine converts transport data from !
679 ! NEOCLASSIC to CORETRANSP CPO !
680 !-------------------------------------------------------!
681 ! Source: --- !
682 ! Developers: D.Kalupin !
683 ! Kontacts: D.Kalupin@fz-juelich.de !
684 ! !
685 ! Comments: should be udated after NCLASS !
686 ! is available to the ETS !
687 ! !
688 !-------------------------------------------------------!
689 
690 
691  USE euitm_schemas
692  USE itm_constants
693  USE copy_structures
694  USE deallocate_structures
696 
697  IMPLICIT NONE
698 
699  TYPE (type_neoclassic), POINTER :: neoclassic(:)
700  TYPE (type_coretransp), POINTER :: coretransp(:)
701  TYPE (type_compositions_type) :: compositions
702 
703  INTEGER, PARAMETER :: nslice = 1 !number of CPO ocurancies in the work flow
704  INTEGER :: nrho
705  INTEGER :: nnucl
706  INTEGER :: nion, iion
707  INTEGER :: nimp, iimp, izimp
708  INTEGER, ALLOCATABLE :: nzimp(:)
709  INTEGER :: nneut
710  INTEGER, ALLOCATABLE :: ncomp(:)
711  INTEGER, ALLOCATABLE :: ntype(:)
712 
713 
714 
715 !-------------------------------------------------------!
716 
717 
718  nrho = SIZE (neoclassic(1)%rho_tor)
719  CALL get_comp_dimensions(neoclassic(1)%COMPOSITIONS, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp)
720 
721 
722 
723 
724  ALLOCATE (coretransp(1))
725  ALLOCATE (coretransp(1)%VALUES(1))
726 
727 
728 
729 ! ++ Toroidal flux coordinate:
730  IF (ASSOCIATED(neoclassic(1)%rho_tor)) THEN
731  ALLOCATE (coretransp(1)%VALUES(1)%rho_tor(nrho))
732  coretransp(1)%VALUES(1)%rho_tor = neoclassic(1)%rho_tor
733  END IF
734 
735 
736 
737 ! ++ Compositions:
738  IF (ASSOCIATED(neoclassic(1)%compositions%nuclei)) THEN
739  CALL deallocate_cpo(coretransp(1)%compositions)
740  CALL copy_cpo(neoclassic(1)%compositions, coretransp(1)%compositions)
741  ELSE
742  ALLOCATE (nzimp(nimp))
743  ALLOCATE (ncomp(nneut))
744  ALLOCATE (ntype(nneut))
745  CALL allocate_compositions(nslice, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, compositions)
746  CALL deallocate_cpo(coretransp(1)%compositions)
747  CALL copy_cpo(compositions, coretransp(1)%compositions)
748  END IF
749 
750 
751 
752 ! ++ sigma
753  IF (ASSOCIATED(neoclassic(1)%sigma)) THEN
754  ALLOCATE(coretransp(1)%VALUES(1)%sigma(nrho))
755  CALL l3interp(neoclassic(1)%sigma, neoclassic(1)%rho_tor, nrho, &
756  coretransp(1)%VALUES(1)%sigma, coretransp(1)%VALUES(1)%rho_tor, nrho)
757  END IF
758 
759 
760 
761 ! ++ ni
762  IF (ASSOCIATED(neoclassic(1)%ni_neo%diff_eff)) THEN
763  ALLOCATE(coretransp(1)%VALUES(1)%ni_transp%diff_eff(nrho,nion,3))
764  coretransp(1)%VALUES(1)%ni_transp%diff_eff = 0.0_r8
765  DO iion=1,nion
766  CALL l3interp(neoclassic(1)%ni_neo%diff_eff(:,iion), neoclassic(1)%rho_tor, nrho, &
767  coretransp(1)%VALUES(1)%ni_transp%diff_eff(:,iion,3), coretransp(1)%VALUES(1)%rho_tor, nrho)
768  END DO
769  END IF
770 
771  IF (ASSOCIATED(neoclassic(1)%ni_neo%vconv_eff)) THEN
772  ALLOCATE(coretransp(1)%VALUES(1)%ni_transp%vconv_eff(nrho,nion,3))
773  coretransp(1)%VALUES(1)%ni_transp%vconv_eff = 0.0_r8
774  DO iion=1,nion
775  CALL l3interp(neoclassic(1)%ni_neo%vconv_eff(:,iion), neoclassic(1)%rho_tor, nrho, &
776  coretransp(1)%VALUES(1)%ni_transp%vconv_eff(:,iion,3), coretransp(1)%VALUES(1)%rho_tor, nrho)
777  END DO
778  END IF
779 
780 
781 
782 ! ++ ne
783  IF (ASSOCIATED(neoclassic(1)%ne_neo%diff_eff)) THEN
784  ALLOCATE(coretransp(1)%VALUES(1)%ne_transp%diff_eff(nrho,3))
785  coretransp(1)%VALUES(1)%ne_transp%diff_eff = 0.0_r8
786  CALL l3interp(neoclassic(1)%ne_neo%diff_eff, neoclassic(1)%rho_tor, nrho, &
787  coretransp(1)%VALUES(1)%ne_transp%diff_eff(:,3), coretransp(1)%VALUES(1)%rho_tor, nrho)
788  END IF
789 
790  IF (ASSOCIATED(neoclassic(1)%ne_neo%vconv_eff)) THEN
791  ALLOCATE(coretransp(1)%VALUES(1)%ne_transp%vconv_eff(nrho,3))
792  coretransp(1)%VALUES(1)%ne_transp%vconv_eff=0.0_r8
793  CALL l3interp(neoclassic(1)%ne_neo%vconv_eff, neoclassic(1)%rho_tor, nrho, &
794  coretransp(1)%VALUES(1)%ne_transp%vconv_eff(:,3), coretransp(1)%VALUES(1)%rho_tor, nrho)
795  END IF
796 
797 
798 
799 ! ++ Ti
800  IF (ASSOCIATED(neoclassic(1)%ti_neo%diff_eff)) THEN
801  ALLOCATE(coretransp(1)%VALUES(1)%ti_transp%diff_eff(nrho,nion))
802  DO iion=1,nion
803  CALL l3interp(neoclassic(1)%ti_neo%diff_eff(:,iion), neoclassic(1)%rho_tor, nrho, &
804  coretransp(1)%VALUES(1)%ti_transp%diff_eff(:,iion), coretransp(1)%VALUES(1)%rho_tor, nrho)
805  END DO
806  END IF
807 
808  IF (ASSOCIATED(neoclassic(1)%Ti_neo%vconv_eff)) THEN
809  ALLOCATE(coretransp(1)%VALUES(1)%Ti_transp%vconv_eff(nrho,nion))
810  DO iion=1,nion
811  CALL l3interp(neoclassic(1)%Ti_neo%vconv_eff(:,iion), neoclassic(1)%rho_tor, nrho, &
812  coretransp(1)%VALUES(1)%Ti_transp%vconv_eff(:,iion), coretransp(1)%VALUES(1)%rho_tor, nrho)
813  END DO
814  END IF
815 
816 
817 
818 ! ++ Te
819  IF (ASSOCIATED(neoclassic(1)%te_neo%diff_eff)) THEN
820  ALLOCATE(coretransp(1)%VALUES(1)%te_transp%diff_eff(nrho))
821  CALL l3interp(neoclassic(1)%te_neo%diff_eff, neoclassic(1)%rho_tor, nrho, &
822  coretransp(1)%VALUES(1)%te_transp%diff_eff, coretransp(1)%VALUES(1)%rho_tor, nrho)
823  END IF
824 
825  IF (ASSOCIATED(neoclassic(1)%Te_neo%vconv_eff)) THEN
826  ALLOCATE(coretransp(1)%VALUES(1)%Te_transp%vconv_eff(nrho))
827  CALL l3interp(neoclassic(1)%Te_neo%vconv_eff, neoclassic(1)%rho_tor, nrho, &
828  coretransp(1)%VALUES(1)%Te_transp%vconv_eff, coretransp(1)%VALUES(1)%rho_tor, nrho)
829  END IF
830 
831 
832 
833 ! ++ vtor/mtor
834 
835 
836 
837 ! ++ nz
838  IF (ASSOCIATED(neoclassic(1)%nz_neo)) THEN
839  ALLOCATE(coretransp(1)%VALUES(1)%nz_transp(nimp))
840  DO iimp = 1, nimp
841  IF (ASSOCIATED(neoclassic(1)%nz_neo(iimp)%diff_eff)) THEN
842  ALLOCATE(coretransp(1)%VALUES(1)%nz_transp(iimp)%diff_eff(nrho,nzimp(iimp)))
843  coretransp(1)%VALUES(1)%nz_transp(iimp)%diff_eff = 0.0_r8
844  DO izimp=1,nzimp(iimp)
845  CALL l3interp(neoclassic(1)%nz_neo(iimp)%diff_eff(:,izimp), neoclassic(1)%rho_tor, nrho, &
846  coretransp(1)%VALUES(1)%nz_transp(iimp)%diff_eff(:,izimp), coretransp(1)%VALUES(1)%rho_tor, nrho)
847  END DO
848  END IF
849 
850  IF (ASSOCIATED(neoclassic(1)%nz_neo(iimp)%vconv_eff)) THEN
851  ALLOCATE(coretransp(1)%VALUES(1)%nz_transp(iimp)%vconv_eff(nrho,nzimp(iimp)))
852  coretransp(1)%VALUES(1)%nz_transp(iimp)%vconv_eff = 0.0_r8
853  DO izimp=1,nzimp(iimp)
854  CALL l3interp(neoclassic(1)%nz_neo(iimp)%vconv_eff(:,izimp), neoclassic(1)%rho_tor, nrho, &
855  coretransp(1)%VALUES(1)%nz_transp(iimp)%vconv_eff(:,izimp), coretransp(1)%VALUES(1)%rho_tor, nrho)
856  END DO
857  END IF
858 
859  IF (ASSOCIATED(neoclassic(1)%nz_neo(iimp)%flux)) THEN
860  ALLOCATE(coretransp(1)%VALUES(1)%nz_transp(iimp)%flux(nrho,nzimp(iimp)))
861  coretransp(1)%VALUES(1)%nz_transp(iimp)%flux = 0.0_r8
862  DO izimp=1,nzimp(iimp)
863  CALL l3interp(neoclassic(1)%nz_neo(iimp)%flux(:,izimp), neoclassic(1)%rho_tor, nrho, &
864  coretransp(1)%VALUES(1)%nz_transp(iimp)%flux(:,izimp), coretransp(1)%VALUES(1)%rho_tor, nrho)
865  END DO
866  END IF
867  END DO
868  END IF
869 
870 
871 
872 
873 !+++ ADD IDENTIFIER TO OUTPUT CPO VALUES(1):
874  ALLOCATE (coretransp(1)%VALUES(1)%transportid%id(1))
875  ALLOCATE (coretransp(1)%VALUES(1)%transportid%description(1))
876  coretransp(1)%VALUES(1)%transportid%id = 'neoclassical'
877  coretransp(1)%VALUES(1)%transportid%flag = 2
878  coretransp(1)%VALUES(1)%transportid%description = 'Neoclassical'
879 
880 
881 
882 
883 
884  RETURN
885 
886 
887  END SUBROUTINE convert_neoclassic2coretransp
888 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
889 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
890 
891 
892 
893 
894 
895 
896 
897 
898 
899 
900 
901 
902 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
903 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
904 !-------------------------------------------------------!
905 !-------------------------------------------------------!
906  SUBROUTINE convert_neoclassic2coresource(NEOCLASSIC, CORESOURCE)
907 !-------------------------------------------------------!
908 ! This routine converts sourceort data from !
909 ! NEOCLASSIC to CORESOURCE CPO !
910 !-------------------------------------------------------!
911 ! Source: --- !
912 ! Developers: D.Kalupin !
913 ! Kontacts: D.Kalupin@fz-juelich.de !
914 ! !
915 ! Comments: should be udated after NCLASS !
916 ! is available to the ETS !
917 ! !
918 !-------------------------------------------------------!
919 
920 
921  USE euitm_schemas
922  USE itm_constants
923  USE copy_structures
924  USE deallocate_structures
926 
927  IMPLICIT NONE
928 
929  TYPE (type_neoclassic), POINTER :: neoclassic(:)
930  TYPE (type_coresource), POINTER :: coresource(:)
931  TYPE (type_compositions_type) :: compositions
932 
933  INTEGER, PARAMETER :: nslice = 1 !number of CPO ocurancies in the work flow
934  INTEGER :: nrho
935  INTEGER :: nnucl = 1
936  INTEGER :: nion = 1
937  INTEGER :: nimp = 0
938  INTEGER, ALLOCATABLE :: nzimp(:)
939  INTEGER :: nneut = 0
940  INTEGER, ALLOCATABLE :: ncomp(:)
941  INTEGER, ALLOCATABLE :: ntype(:)
942 
943 
944 
945 
946 !-------------------------------------------------------!
947 
948 
949  nrho = SIZE(neoclassic(1)%rho_tor)
950  CALL get_comp_dimensions(neoclassic(1)%COMPOSITIONS, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp)
951 
952 
953 
954  ALLOCATE (coresource(1))
955  ALLOCATE (coresource(1)%VALUES(1))
956 
957 
958 
959 ! ++ Toroidal flux coordinate:
960  IF (ASSOCIATED(neoclassic(1)%rho_tor)) THEN
961  ALLOCATE (coresource(1)%VALUES(1)%rho_tor(nrho))
962  coresource(1)%VALUES(1)%rho_tor = neoclassic(1)%rho_tor
963  END IF
964 
965 
966 
967 ! ++ Compositions:
968  IF (ASSOCIATED(neoclassic(1)%compositions%nuclei)) THEN
969  CALL deallocate_cpo(coresource(1)%compositions)
970  CALL copy_cpo(neoclassic(1)%compositions, coresource(1)%compositions)
971  ELSE
972  ALLOCATE (nzimp(nimp))
973  ALLOCATE (ncomp(nneut))
974  ALLOCATE (ntype(nneut))
975  CALL allocate_compositions(nslice, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, compositions)
976  CALL deallocate_cpo(coresource(1)%compositions)
977  CALL copy_cpo(compositions, coresource(1)%compositions)
978  END IF
979 
980 
981 
982 ! ++ Bootstrap current:
983  IF (ASSOCIATED(neoclassic(1)%jboot)) THEN
984  ALLOCATE(coresource(1)%VALUES(1)%j(nrho))
985  coresource(1)%VALUES(1)%j = neoclassic(1)%jboot
986  END IF
987 
988 
989 
990 
991 
992 ! +++ ADD IDENTIFIER TO OUTPUT CPO VALUES(1):
993  ALLOCATE (coresource(1)%VALUES(1)%sourceid%id(1))
994  ALLOCATE (coresource(1)%VALUES(1)%sourceid%description(1))
995  coresource(1)%VALUES(1)%sourceid%id = 'neoclassical'
996  coresource(1)%VALUES(1)%sourceid%flag = 32
997  coresource(1)%VALUES(1)%sourceid%description = 'Neoclassical'
998 
999 
1000 
1001  RETURN
1002 
1003 
1004  END SUBROUTINE convert_neoclassic2coresource
1005 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1006 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1007 
1008 
1009 
1010 
1011 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1012 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1013  SUBROUTINE changeradii (EQUILIBRIUM, &
1014  coreprof, &
1015  coretransp, &
1016  coresource, &
1017  coreimpur, &
1018  coreneutrals, &
1019  neoclassic)
1020 
1021 ! +++ Declaration of variables:
1022  USE itm_types
1023  USE euitm_schemas
1025  USE copy_structures
1026 
1027 
1028 ! +++ CPO derived types:
1029  TYPE (type_equilibrium), POINTER :: equilibrium(:) !input CPO
1030 
1031  TYPE (type_coreprof), POINTER :: coreprof(:) !input CPO
1032  TYPE (type_coretransp), POINTER :: coretransp(:) !input CPO
1033  TYPE (type_coresource), POINTER :: coresource(:) !input CPO
1034  TYPE (type_coreimpur), POINTER :: coreimpur(:) !input CPO
1035  TYPE (type_coreneutrals), POINTER :: coreneutrals(:) !input CPO
1036  TYPE (type_neoclassic), POINTER :: neoclassic(:) !input CPO
1037 
1038  REAL(R8) :: rho_tor_rescale
1039  INTEGER(ITM_I4) :: neq
1040 
1041 
1042  neq = SIZE(equilibrium(1)%profiles_1d%rho_tor)
1043 
1044 ! +++ Copy input CPOs to output CPOs:
1045  rho_tor_rescale = 1.0_r8
1046  IF (ASSOCIATED(coreprof(1)%rho_tor)) THEN
1047  IF (maxval(coreprof(1)%rho_tor).GE.equilibrium(1)%profiles_1d%rho_tor(neq)*0.5_r8) &
1048  rho_tor_rescale = equilibrium(1)%profiles_1d%rho_tor(neq) / &
1049  coreprof(1)%rho_tor(SIZE(coreprof(1)%rho_tor))
1050  coreprof(1)%rho_tor = coreprof(1)%rho_tor * rho_tor_rescale
1051  END IF
1052 
1053 
1054  rho_tor_rescale = 1.0_r8
1055  IF (ASSOCIATED(coretransp(1)%VALUES)) THEN
1056  IF (ASSOCIATED(coretransp(1)%VALUES(1)%rho_tor)) THEN
1057  IF (maxval(coretransp(1)%VALUES(1)%rho_tor).GE.equilibrium(1)%profiles_1d%rho_tor(neq)*0.5_r8) &
1058  rho_tor_rescale = equilibrium(1)%profiles_1d%rho_tor(neq) / &
1059  coretransp(1)%VALUES(1)%rho_tor(SIZE(coretransp(1)%VALUES(1)%rho_tor))
1060  coretransp(1)%VALUES(1)%rho_tor = coretransp(1)%VALUES(1)%rho_tor * rho_tor_rescale
1061  END IF
1062  END IF
1063 
1064 
1065  rho_tor_rescale = 1.0_r8
1066  IF (ASSOCIATED(coresource(1)%VALUES)) THEN
1067  IF (ASSOCIATED(coresource(1)%VALUES(1)%rho_tor)) THEN
1068  IF (maxval(coresource(1)%VALUES(1)%rho_tor).GE.equilibrium(1)%profiles_1d%rho_tor(neq)*0.5_r8) &
1069  rho_tor_rescale = equilibrium(1)%profiles_1d%rho_tor(neq) / &
1070  coresource(1)%VALUES(1)%rho_tor(SIZE(coresource(1)%VALUES(1)%rho_tor))
1071  coresource(1)%VALUES(1)%rho_tor = coresource(1)%VALUES(1)%rho_tor * rho_tor_rescale
1072  END IF
1073  END IF
1074 
1075 
1076  rho_tor_rescale = 1.0_r8
1077  IF (ASSOCIATED(coreimpur(1)%rho_tor)) THEN
1078  IF (maxval(coreimpur(1)%rho_tor).GE.equilibrium(1)%profiles_1d%rho_tor(neq)*0.5_r8) &
1079  rho_tor_rescale = equilibrium(1)%profiles_1d%rho_tor(neq) / &
1080  coreimpur(1)%rho_tor(SIZE(coreimpur(1)%rho_tor))
1081  coreimpur(1)%rho_tor = coreimpur(1)%rho_tor * rho_tor_rescale
1082  END IF
1083 
1084  rho_tor_rescale = 1.0_r8
1085  IF(ASSOCIATED(coreneutrals(1)%rho_tor)) THEN
1086  IF (maxval(coreneutrals(1)%rho_tor).GE.equilibrium(1)%profiles_1d%rho_tor(neq)*0.5_r8) &
1087  rho_tor_rescale = equilibrium(1)%profiles_1d%rho_tor(neq) / &
1088  coreneutrals(1)%rho_tor(SIZE(coreneutrals(1)%rho_tor))
1089  coreneutrals(1)%rho_tor = coreneutrals(1)%rho_tor * rho_tor_rescale
1090  ENDIF
1091 
1092  rho_tor_rescale = 1.0_r8
1093  IF(ASSOCIATED(neoclassic(1)%rho_tor)) THEN
1094  IF (maxval(neoclassic(1)%rho_tor).GE.equilibrium(1)%profiles_1d%rho_tor(neq)*0.5_r8) &
1095  rho_tor_rescale = equilibrium(1)%profiles_1d%rho_tor(neq) / &
1096  neoclassic(1)%rho_tor(SIZE(neoclassic(1)%rho_tor))
1097  neoclassic(1)%rho_tor = neoclassic(1)%rho_tor * rho_tor_rescale
1098  END IF
1099 
1100 
1101  RETURN
1102 
1103  END SUBROUTINE changeradii
1104 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1105 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1106 
1107 
1108 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1109 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1110 SUBROUTINE interpolate_impur_convert(COREIMPUR_IN, COREIMPUR_OUT)
1111 !-------------------------------------------------------!
1112 ! This routine interpolates impurity !
1113 ! using rho_tor_norm grid !
1114 !-------------------------------------------------------!
1115 ! Source: --- !
1116 ! Developers: D.Kalupin !
1117 ! Kontacts: D.Kalupin@fz-juelich.de !
1118 ! !
1119 ! !
1120 !-------------------------------------------------------!
1121 
1122  USE euitm_schemas
1123  USE itm_types
1125 
1126  IMPLICIT NONE
1127 
1128  TYPE (type_coreimpur) :: coreimpur_in
1129  TYPE (type_coreimpur) :: coreimpur_out
1130 
1131  INTEGER :: nrho1, nrho2
1132  INTEGER :: irho1, irho2
1133  INTEGER :: nnucl1,inucl1
1134  INTEGER :: nnucl2,inucl2
1135  INTEGER :: nion1, iion1
1136  INTEGER :: nion2, iion2
1137  INTEGER :: nimp1, iimp1
1138  INTEGER :: nimp2, iimp2
1139  INTEGER, ALLOCATABLE :: nzimp1(:)
1140  INTEGER, ALLOCATABLE :: nzimp2(:)
1141  INTEGER :: izimp1,izimp2
1142  INTEGER :: nneut1,ineut1
1143  INTEGER :: nneut2,ineut2
1144  INTEGER, ALLOCATABLE :: ncomp1(:)
1145  INTEGER, ALLOCATABLE :: ncomp2(:)
1146  INTEGER, ALLOCATABLE :: ntype1(:)
1147  INTEGER, ALLOCATABLE :: ntype2(:)
1148 
1149  REAL (R8), ALLOCATABLE :: rho_norm(:), rho_norm_imp(:)
1150  REAL (R8) :: zmin1, zmin2
1151  REAL (R8) :: zmax1, zmax2
1152 
1153 !==============================================
1154 
1155 
1156 
1157  nrho1 = SIZE(coreimpur_out%rho_tor)
1158  nrho2 = SIZE(coreimpur_in%rho_tor)
1159 
1160  ALLOCATE (rho_norm(nrho1))
1161  ALLOCATE (rho_norm_imp(nrho2))
1162 
1163  rho_norm = coreimpur_out%rho_tor_norm
1164 
1165  IF(ASSOCIATED(coreimpur_in%rho_tor_norm).AND.coreimpur_in%rho_tor_norm(nrho2).EQ.1.0_r8) THEN
1166  rho_norm_imp = coreimpur_in%rho_tor_norm
1167  ELSE
1168  rho_norm_imp =coreimpur_in%rho_tor/coreimpur_in%rho_tor(nrho2)
1169  END IF
1170 
1171 
1172  CALL get_comp_dimensions(coreimpur_out%COMPOSITIONS, nnucl1, nion1, nimp1, nzimp1, nneut1, ntype1, ncomp1)
1173  CALL get_comp_dimensions(coreimpur_in%COMPOSITIONS, nnucl2, nion2, nimp2, nzimp2, nneut2, ntype2, ncomp2)
1174 
1175 
1176 
1177 ! +++ IMPURITY
1178  IF (nimp1*nimp2.LE.0) goto 8
1179  output_impurity_loop: DO iimp1 = 1, nimp1
1180  inucl1 = coreimpur_out%COMPOSITIONS%IMPURITIES(iimp1)%nucindex
1181 
1182 
1183  coreimpur_out%IMPURITY(iimp1)%nz = 0.0_r8
1184  coreimpur_out%IMPURITY(iimp1)%flux%flux_dv = 0.0_r8
1185 
1186  input_impurity_loop: DO iimp2 = 1, nimp2
1187  inucl2 = coreimpur_in%COMPOSITIONS%IMPURITIES(iimp2)%nucindex
1188 
1189  IF (inucl2.LE.0 .OR. inucl2.GT.SIZE(coreimpur_in%COMPOSITIONS%NUCLEI)) goto 7
1190 
1191  check_impurity_consistency: IF &
1192  (abs(coreimpur_out%COMPOSITIONS%NUCLEI(inucl1)%amn - coreimpur_in%COMPOSITIONS%NUCLEI(inucl2)%amn) .LE. 0.25 .AND. &
1193  abs(coreimpur_out%COMPOSITIONS%NUCLEI(inucl1)%zn - coreimpur_in%COMPOSITIONS%NUCLEI(inucl2)%zn ) .LE. 0.25 ) THEN
1194 
1195  output_ionzation_state: DO izimp1 = 1, nzimp1(iimp1)
1196  input_ionzation_state: DO izimp2 = 1, nzimp2(iimp2)
1197 
1198  zmin1 = coreimpur_out%COMPOSITIONS%IMPURITIES(iimp1)%zmin(izimp1)
1199  zmax1 = coreimpur_out%COMPOSITIONS%IMPURITIES(iimp1)%zmax(izimp1)
1200  zmin2 = coreimpur_in%COMPOSITIONS%IMPURITIES(iimp2)%zmin(izimp2)
1201  zmax2 = coreimpur_in%COMPOSITIONS%IMPURITIES(iimp2)%zmax(izimp2)
1202 
1203  check_ionzation_state_consistency: if&
1204  (abs((zmax1+zmin1)/2.0 - (zmax2+zmin2)/2.0).LE. 0.25) THEN
1205 ! nz
1206  IF(ASSOCIATED(coreimpur_in%IMPURITY(iimp2)%nz)) &
1207  CALL l3interp(coreimpur_in%IMPURITY(iimp2)%nz(:,izimp2), rho_norm_imp, nrho2, &
1208  coreimpur_out%IMPURITY(iimp1)%nz(:,izimp1), rho_norm, nrho1)
1209  IF(ASSOCIATED(coreimpur_in%IMPURITY(iimp2)%flux%flux_dv)) &
1210  CALL l3interp(coreimpur_in%IMPURITY(iimp2)%flux%flux_dv(:,izimp2), rho_norm_imp, nrho2, &
1211  coreimpur_out%IMPURITY(iimp1)%flux%flux_dv(:,izimp1), rho_norm, nrho1)
1212 ! tz
1213  IF(ASSOCIATED(coreimpur_in%IMPURITY(iimp2)%tz)) &
1214  CALL l3interp(coreimpur_in%IMPURITY(iimp2)%tz(:,izimp2), rho_norm_imp, nrho2, &
1215  coreimpur_out%IMPURITY(iimp1)%tz(:,izimp1), rho_norm, nrho1)
1216 ! z
1217  IF(ASSOCIATED(coreimpur_in%IMPURITY(iimp2)%z)) &
1218  CALL l3interp(coreimpur_in%IMPURITY(iimp2)%z(:,izimp2), rho_norm_imp, nrho2, &
1219  coreimpur_out%IMPURITY(iimp1)%z(:,izimp1), rho_norm, nrho1)
1220 ! zsq
1221  IF(ASSOCIATED(coreimpur_in%IMPURITY(iimp2)%zsq)) &
1222  CALL l3interp(coreimpur_in%IMPURITY(iimp2)%zsq(:,izimp2), rho_norm_imp, nrho2, &
1223  coreimpur_out%IMPURITY(iimp1)%zsq(:,izimp1), rho_norm, nrho1)
1224 ! radiation
1225  IF(ASSOCIATED(coreimpur_in%IMPURITY(iimp2)%diagnostic%radiation%line_rad%profile)) &
1226  CALL l3interp(coreimpur_in%IMPURITY(iimp2)%diagnostic%radiation%line_rad%profile(:,izimp2), rho_norm_imp, nrho2, &
1227  coreimpur_out%IMPURITY(iimp1)%diagnostic%radiation%line_rad%profile(:,izimp1), rho_norm, nrho1)
1228  IF(ASSOCIATED(coreimpur_in%IMPURITY(iimp2)%diagnostic%radiation%brem_radrec%profile)) &
1229  CALL l3interp(coreimpur_in%IMPURITY(iimp2)%diagnostic%radiation%brem_radrec%profile(:,izimp2), rho_norm_imp, nrho2, &
1230  coreimpur_out%IMPURITY(iimp1)%diagnostic%radiation%brem_radrec%profile(:,izimp1), rho_norm, nrho1)
1231  IF(ASSOCIATED(coreimpur_in%IMPURITY(iimp2)%diagnostic%radiation%sum%profile)) &
1232  CALL l3interp(coreimpur_in%IMPURITY(iimp2)%diagnostic%radiation%sum%profile(:,izimp2), rho_norm_imp, nrho2, &
1233  coreimpur_out%IMPURITY(iimp1)%diagnostic%radiation%sum%profile(:,izimp1), rho_norm, nrho1)
1234  END IF check_ionzation_state_consistency
1235 
1236  END DO input_ionzation_state
1237  END DO output_ionzation_state
1238 
1239  ENDIF check_impurity_consistency
1240 
1241 7 CONTINUE
1242 
1243  END DO input_impurity_loop
1244  END DO output_impurity_loop
1245 
1246 
1247 
1248 
1249 
1250 
1251 
1252 
1253 8 IF(ALLOCATED(nzimp1)) DEALLOCATE (nzimp1)
1254  IF(ALLOCATED(ncomp1)) DEALLOCATE (ncomp1)
1255  IF(ALLOCATED(ntype1)) DEALLOCATE (ntype1)
1256  IF(ALLOCATED(nzimp2)) DEALLOCATE (nzimp2)
1257  IF(ALLOCATED(ncomp2)) DEALLOCATE (ncomp2)
1258  IF(ALLOCATED(ntype2)) DEALLOCATE (ntype2)
1259 
1260  IF(ALLOCATED(rho_norm)) DEALLOCATE (rho_norm)
1261  IF(ALLOCATED(rho_norm_imp)) DEALLOCATE (rho_norm_imp)
1262 
1263 
1264 
1265  RETURN
1266 
1267  END SUBROUTINE interpolate_impur_convert
1268 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1269 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1270 
1271 END MODULE convert
subroutine l3deriv(y_in, x_in, nr_in, dydx_out, x_out, nr_out)
Definition: l3interp.f90:59
subroutine convert_cpo_to_internal_types(EQUILIBRIUM_OLD, EQUILIBRIUM_ITER, COREPROF_OLD, COREPROF_ITER,CORETRANSP, CORESOURCE, COREIMPUR, COREFAST,CONTROL_INTEGER, CONTROL_DOUBLE,
Definition: convert.f90:13
subroutine convert_neoclassic2coresource(NEOCLASSIC, CORESOURCE)
Definition: convert.f90:906
subroutine changeradii(EQUILIBRIUM, COREPROF, CORETRANSP, CORESOURCE, COREIMPUR, CORENEUTRALS, NEOCLASSIC)
Definition: convert.f90:1013
subroutine allocate_compositions(NSLICE, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP, COMPOSITIONS)
IMPURITY.
Definition: impurity.F90:8
subroutine allocate_coreimpur_cpo(NSLICE, NRHO, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP, COREIMPUR)
This routine allocates COREIMPUR CPO.
Module converts to/from CPOs to ETS types.
Definition: convert.f90:8
subroutine profiles(p0, rbphi, dp0, drbphi, a)
Definition: profiles.f90:1
subroutine get_comp_dimensions(COMPOSITIONS, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP)
subroutine convert_internal_to_cpo_types(GEOMETRY, PROFILES, TRANSPORT, SOURCES, GLOBAL, COREPROF, DIAG)
This routine converts ETS into the CPOs derived types.
Definition: convert.f90:503
subroutine l3interp(y_in, x_in, nr_in, y_out, x_out, nr_out)
Definition: l3interp.f90:1
subroutine convert_neoclassic2coretransp(NEOCLASSIC, CORETRANSP)
Definition: convert.f90:676
This module contains routines for allocation/deallocation if CPOs used in ETS.
subroutine interpolate_impur_convert(COREIMPUR_IN, COREIMPUR_OUT)
Definition: convert.f90:1110
The module declares types of variables used in ETS (transport code)
Definition: ets_plasma.f90:8
subroutine evolution(T, R_in, R_out, El, Tr_l, Tr_U, Ip)