ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
ets.F90
Go to the documentation of this file.
1 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
7 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
8 MODULE ets
9 
10 CONTAINS
11 
12 
13 
14 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
23 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
24 
25  SUBROUTINE itm_ets (COREPROF_OLD, COREPROF_ITER, COREPROF_NEW, &
26  equilibrium_old, equilibrium_iter, &
27  coretransp, coresource, coreimpur, &
28  control_integer, control_double, code_parameters)
29 
30 !-------------------------------------------------------!
31 ! This routine provides interface between CPO !
32 ! dderived types and internal ETS derived types. !
33 !-------------------------------------------------------!
34 ! Source: --- !
35 ! Developers: D.Kalupin !
36 ! Kontacts: D.Kalupin@fz-juelich.de !
37 ! !
38 ! Comments: might change after the ITM !
39 ! data stucture is finalized !
40 ! !
41 !-------------------------------------------------------!
42 
43 
44  USE euitm_schemas
45  USE copy_structures
46  USE ets_plasma
47  USE convert
49 
50  IMPLICIT NONE
51 
52  INTEGER :: ifail
53 
54 ! +++ CPO derived types:
55  TYPE (type_equilibrium), POINTER :: equilibrium_old(:) !input CPO with geometry quantities from previous time
56  TYPE (type_equilibrium), POINTER :: equilibrium_iter(:) !input CPO with geometry quantities from previous iteration
57  TYPE (type_coreprof), POINTER :: coreprof_old(:) !input CPO with internal ETS parameters profiles from previous time
58  TYPE (type_coreprof), POINTER :: coreprof_new(:) !input/output CPO with internal ETS parameters profiles
59  TYPE (type_coreprof), POINTER :: coreprof_iter(:) !input/output CPO with internal ETS parameters profiles from previous iteration
60  TYPE (type_coretransp), POINTER :: coretransp(:) !input CPO with transport coefficients
61  TYPE (type_coresource), POINTER :: coresource(:) !input CPO with sources
62  TYPE (type_coreimpur), POINTER :: coreimpur(:) !input CPO with impurities
63  TYPE (type_corefast), POINTER :: corefast(:) => null() !input CPO with fast particles profiles
64  TYPE (type_param) :: code_parameters
65  INTEGER(ITM_I4) :: return_status
66 
67 
68 ! +++ Internal ETS derived types:
69  TYPE (magnetic_geometry) :: geometry !contains all geometry quantities
70  TYPE (plasma_profiles) :: profiles !contains profiles of plasma parameters
71  TYPE (transport_coefficients) :: transport !contains profiles of trasport coefficients
72  TYPE (sources_and_sinks) :: sources !contains profiles of sources
73  TYPE (time_evolution) :: evolution !contains all parameters required by time evolution
74  TYPE (run_control) :: control !contains all parameters required by run
75  TYPE (impurity_profiles) :: impurity !contains profiles of impurities calculated by separate module
76  TYPE (global_param) :: global !contains global plasma parameters
77  TYPE (diagnostic) :: diag !contains error messages and warnings
78 
79 ! +++ Dimensions:
80  INTEGER, PARAMETER :: nocur = 1 !number of CPO ocurancies in the work flow
81  INTEGER :: nrho,irho !number of radial points (input, determined from COREPROF CPO)
82  INTEGER :: nion !number of ion species (input, determined from COREPROF CPO)
83  INTEGER :: nimp !number of impurity species (input, determined from COREIMPUR CPO)
84  INTEGER, ALLOCATABLE :: nzimp(:) !maximum number of impurity ionization states
85  INTEGER :: iimp, max_nzimp
86 
87 ! +++ Control parameters:
88  INTEGER :: control_integer(4) !integer control parameters
89  REAL (R8) :: control_double(6) !real control parameters
90 
91 ! +++ codeparam quantities:
92  REAL (R8) :: rhon !effective minor radius
93  INTEGER :: solver_type !representation of transport equations
94  INTEGER :: sigma_source !origin of Plasma electrical conductivity
95  INTEGER :: quasi_neut
96  REAL (R8) :: amix !mixing factor
97  REAL (R8) :: amixtr !mixing factor for profiles
98  INTEGER :: psi_bnd_type !Type of boundary conditions current
99  INTEGER :: ni_bnd_type !Type of boundary conditions ion density
100  INTEGER :: ti_bnd_type !Type of boundary conditions ion temperature
101  INTEGER :: te_bnd_type !Type of boundary conditions electron temperature
102  INTEGER :: vtor_bnd_type !Type of boundary conditions toroidal rotation
103 
104 ! +++ control parameters
105  INTEGER, SAVE :: debug_level=0 !debug level
106  REAL (R8), SAVE :: ohmic_heating_multiplier=1.0_r8
107 
108 ! +++
109  LOGICAL, SAVE :: first=.true.
110  CHARACTER(LEN=500) :: failstring
111 ! +++ Set dimensions:
112 
113 ! +++ Stabilization scheme !AF 25.Apr.2016, 22.Aug.2016
114  REAL (R8), PARAMETER, DIMENSION(2) :: hyper_diff = (/ 0.0_r8, 0.0_r8 /) !hyper diffusivity
115  !With zero HYPER_DIFF_EXP and HYPER_DIFF_IMP the Fortran
116  !workflow runs without stabilization
117  integer ::j_boun
118 
119  nrho = SIZE (coreprof_iter(1)%rho_tor)
120  nion = SIZE (coreprof_iter(1)%compositions%ions)
121  if(associated(coreimpur)) then
122  nimp = SIZE (coreimpur(1)%compositions%impurities)
123  else
124  nimp = 0
125  endif
126  ALLOCATE (nzimp(nimp))
127  nzimp = 0
128  DO iimp = 1, nimp
129  nzimp(iimp) = coreimpur(1)%compositions%impurities(iimp)%nzimp
130  ENDDO
131 
132  max_nzimp = maxval(nzimp)
133 
134  IF(first) THEN
135  WRITE(*,*) 'Processing ets specific input'
136 
137  solver_type = control_integer(1)
138  sigma_source = control_integer(2)
139  quasi_neut = control_integer(3)
140  amix = control_double(2)
141  amixtr = control_double(3)
142  j_boun= control_integer(4)
143 
144  psi_bnd_type = itm_int_invalid
145  ni_bnd_type = itm_int_invalid
146  ti_bnd_type = itm_int_invalid
147  te_bnd_type = itm_int_invalid
148  vtor_bnd_type = itm_int_invalid
149 
150  CALL assign_code_parameters(code_parameters, return_status)
151 
152  control_integer(1) = solver_type !number of numerical solver
153  control_integer(2) = sigma_source !number of numerical solver
154  control_integer(3) = quasi_neut
155  control_double(2) = amix !mixing factor for profiles
156  control_double(3) = amixtr !mixing factor for transport coefficients
157 
158  IF(psi_bnd_type.NE.itm_int_invalid) coreprof_iter(1)%psi%boundary%type = psi_bnd_type
159  IF(ni_bnd_type.NE.itm_int_invalid) coreprof_iter(1)%ni%boundary%type(:) = ni_bnd_type
160  IF(ti_bnd_type.NE.itm_int_invalid) coreprof_iter(1)%ti%boundary%type(:) = ti_bnd_type
161  IF(te_bnd_type.NE.itm_int_invalid) coreprof_iter(1)%te%boundary%type = te_bnd_type
162  IF(vtor_bnd_type.NE.itm_int_invalid) coreprof_iter(1)%vtor%boundary%type(:) = vtor_bnd_type
163 
164  first = .false.
165 
166  ENDIF
167 
168  ALLOCATE (coreprof_new(1))
169  CALL copy_cpo(coreprof_iter(1),coreprof_new(1))
170 
171 
172 ! +++ Allocation of ETS derived types:
173  CALL allocate_magnetic_geometry(nrho, geometry, ifail)
174  CALL allocate_plasma_profiles(nrho,nion, profiles, ifail)
175  CALL allocate_transport_coefficients(nrho,nion, transport, ifail)
176  CALL allocate_sources_and_sinks(nrho,nion, sources, ifail)
177  CALL allocate_impurity_profiles(nrho,nimp,max_nzimp, impurity, ifail)
178  CALL allocate_global_param( global, ifail)
179  CALL allocate_time_evolution(nrho,nion, evolution, ifail)
180  CALL allocate_run_control( control, ifail)
181 
182 
183 ! +++ Copy CPOs in ETS derived types:
185  (equilibrium_old, equilibrium_iter, coreprof_old, coreprof_iter, &
186  coretransp, coresource, coreimpur, corefast, &
187  control_integer, control_double, &
188 !
189  geometry, profiles, transport, sources, impurity, evolution, &
190  control, j_boun, diag)
191 
192  control%debug_level = debug_level
193  control%ohmic_heating_multiplier = ohmic_heating_multiplier
194 
195 ! +++ Call MAIN_PLASMA with internal ETS derived types:
196  CALL main_plasma &
197  (geometry, profiles, transport, sources, impurity, evolution, control, &
198  hyper_diff, hyper_diff, j_boun,ifail, failstring) !AF 25.Apr.2016, 22.Aug.2016
199 ! ifail,failstring)
200 
201 
202 
203 ! +++ Calculate global quantities:
204  CALL calculate_globals &
205  (geometry, profiles, sources, global, diag)
206 
207 
208 
209 ! +++ Copy ETS derived types in CPOs:
211 ! (GEOMETRY, PROFILES, TRANSPORT, SOURCES, COREPROF_NEW)
212  (geometry, profiles, transport, sources, global, coreprof_new, diag)
213 
214 
215 
216 ! +++ Deallocation of ETS derived types:
217  CALL deallocate_magnetic_geometry(geometry, ifail)
219  CALL deallocate_transport_coefficients(transport, ifail)
220  CALL deallocate_sources_and_sinks(sources, ifail)
223  CALL deallocate_run_control(control, ifail)
224 
225 
226 
227 
228  RETURN
229 
230  CONTAINS
231 
232  SUBROUTINE assign_code_parameters(codeparameters, return_status)
233 
234  !-----------------------------------------------------------------------
235  ! calls the XML parser for the code parameters and assign the
236  ! resulting values to the corresponding variables
237  !TODO: check an alternative and more elegant solution in Perl
238  !-----------------------------------------------------------------------
239 
240  USE mod_f90_kind
241  USE euitm_schemas
242  USE euitm_xml_parser
243 
244  IMPLICIT NONE
245 
246  TYPE (type_param), INTENT(in) :: codeparameters
247  INTEGER(ikind), INTENT(out) :: return_status
248 
249  TYPE(tree) :: parameter_list
250  TYPE(element), POINTER :: temp_pointer
251  INTEGER(ikind) :: i, nparm, n_values
252  CHARACTER(len = 132) :: cname
253 
254  return_status = 0 ! no error
255 
256  !-- parse xml-string codeparameters%parameters
257 
258  WRITE(*,*) 'Calling euitm_xml_parse'
259  CALL euitm_xml_parse(code_parameters, nparm, parameter_list)
260  WRITE(*,*) 'Called euitm_xml_parse'
261 
262  !-- assign variables
263 
264  temp_pointer => parameter_list%first
265 
266  outer: DO
267  cname = char2str(temp_pointer%cname) ! necessary for AIX
268  SELECT CASE (cname)
269  CASE ("parameters")
270  temp_pointer => temp_pointer%child
271  cycle
272 
273 !-- dims parameters
274  CASE ("dims")
275  temp_pointer => temp_pointer%child
276  cycle
277  CASE ("nrho")
278  IF (ALLOCATED(temp_pointer%cvalue)) &
279  CALL char2num(temp_pointer%cvalue, nrho)
280  CASE ("nion")
281  IF (ALLOCATED(temp_pointer%cvalue)) &
282  CALL char2num(temp_pointer%cvalue, nion)
283  CASE ("nimp")
284  IF (ALLOCATED(temp_pointer%cvalue)) &
285  CALL char2num(temp_pointer%cvalue, nimp)
286  CASE ("max_nzimp")
287  IF (ALLOCATED(temp_pointer%cvalue)) &
288  CALL char2num(temp_pointer%cvalue, max_nzimp)
289 
290 !-- solver parameters
291  CASE ("solver")
292  temp_pointer => temp_pointer%child
293  cycle
294  CASE ("rhon")
295  IF (ALLOCATED(temp_pointer%cvalue)) &
296  CALL char2num(temp_pointer%cvalue, rhon)
297  CASE ("solver_type")
298  IF (ALLOCATED(temp_pointer%cvalue)) &
299  CALL char2num(temp_pointer%cvalue, solver_type)
300  CASE ("sigma_source")
301  IF (ALLOCATED(temp_pointer%cvalue)) &
302  CALL char2num(temp_pointer%cvalue, sigma_source)
303  CASE ("amix")
304  IF (ALLOCATED(temp_pointer%cvalue)) &
305  CALL char2num(temp_pointer%cvalue, amix)
306  CASE ("amixtr")
307  IF (ALLOCATED(temp_pointer%cvalue)) &
308  CALL char2num(temp_pointer%cvalue, amixtr)
309  CASE ("debug_level")
310  IF (ALLOCATED(temp_pointer%cvalue)) &
311  CALL char2num(temp_pointer%cvalue, debug_level)
312  CASE ("ohmic_heating_multiplier")
313  IF (ALLOCATED(temp_pointer%cvalue)) &
314  CALL char2num(temp_pointer%cvalue, ohmic_heating_multiplier)
315 
316 !-- boundary parameters
317  CASE ("boundary")
318  temp_pointer => temp_pointer%child
319  cycle
320  CASE ("psi_bnd_type")
321  IF (ALLOCATED(temp_pointer%cvalue)) &
322  CALL char2num(temp_pointer%cvalue, psi_bnd_type)
323  CASE ("ni_bnd_type")
324  IF (ALLOCATED(temp_pointer%cvalue)) &
325  CALL char2num(temp_pointer%cvalue, ni_bnd_type)
326  CASE ("ti_bnd_type")
327  IF (ALLOCATED(temp_pointer%cvalue)) &
328  CALL char2num(temp_pointer%cvalue, ti_bnd_type)
329  CASE ("te_bnd_type")
330  IF (ALLOCATED(temp_pointer%cvalue)) &
331  CALL char2num(temp_pointer%cvalue, te_bnd_type)
332  CASE ("vtor_bnd_type")
333  IF (ALLOCATED(temp_pointer%cvalue)) &
334  CALL char2num(temp_pointer%cvalue, vtor_bnd_type)
335 
336 !-- default
337  CASE default
338  WRITE(*, *) 'ERROR: invalid parameter', cname
339  return_status = 1
340  EXIT
341  END SELECT
342  DO
343  IF (ASSOCIATED(temp_pointer%sibling)) THEN
344  temp_pointer => temp_pointer%sibling
345  EXIT
346  END IF
347  IF (ASSOCIATED(temp_pointer%parent, parameter_list%first )) &
348  EXIT outer
349  IF (ASSOCIATED(temp_pointer%parent)) THEN
350  temp_pointer => temp_pointer%parent
351  ELSE
352  WRITE(*, *) 'ERROR: broken list.'
353  RETURN
354  END IF
355  END DO
356  END DO outer
357 
358  !-- destroy tree
359  CALL destroy_xml_tree(parameter_list)
360 
361  RETURN
362 
363  END SUBROUTINE assign_code_parameters
364 
365  END SUBROUTINE itm_ets
366 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
367 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
368 
369 
370 
371 
372 
373 
374 
375 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
376 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
377 
379 ! OLD: ITER: NEW:
380 ! Previous Previous output
381 ! time step iteration
382  (coreprof_old, coreprof_iter, coreprof_new, & !1-D profiles of plasma parameters
383  equilibrium_old, equilibrium_iter, & !Equilibrium quantities / geometry
384  coretransp_iter, & !transport coefficients
385  coresource_iter, & !sources
386  coreimpur_iter, & !impurity species
387  corefast_iter, & !non-thermal components
388 !
389  control_integer, control_double, & !control switches
390 ! CONTROL_INTEGER, CONTROL_DOUBLE, HYPER_DIFF, ifail, & !AF 25.Apr.2016, 22.Aug.2016
391  hyper_diff, & !AF 25.Apr.2016, 22.Aug.2016
392 ! code_parameters)
393  diag) !run diagnostic (errors)
394 
395 
396 !-------------------------------------------------------!
397 ! This routine provides interface between CPO !
398 ! derived types and internal ETS derived types !
399 ! for KEPLER ETS actor. !
400 !-------------------------------------------------------!
401 ! Source: --- !
402 ! Developers: D.Kalupin !
403 ! Kontacts: D.Kalupin@fz-juelich.de !
404 ! !
405 ! Comments: Code parameters are defined !
406 ! in the Wokflow !
407 ! !
408 !-------------------------------------------------------!
409 
410 
411  USE euitm_schemas
412  USE copy_structures
413  USE ets_plasma
414  USE convert
416 
417  IMPLICIT NONE
418 
419  INTEGER :: ifail
420 
421 ! +++ CPO derived types:
422  TYPE (type_equilibrium), POINTER :: equilibrium_old(:) !input CPO with geometry quantities from previous time
423  TYPE (type_equilibrium), POINTER :: equilibrium_iter(:) !input CPO with geometry quantities from previous iteration
424  TYPE (type_coreprof), POINTER :: coreprof_old(:) !input CPO with internal ETS parameters profiles from previous time
425  TYPE (type_coreprof), POINTER :: coreprof_new(:) !input/output CPO with internal ETS parameters profiles
426  TYPE (type_coreprof), POINTER :: coreprof_iter(:) !input/output CPO with internal ETS parameters profiles from previous iteration
427  TYPE (type_coretransp), POINTER :: coretransp_iter(:) !input CPO with transport coefficients
428  TYPE (type_coresource), POINTER :: coresource_iter(:) !input CPO with sources
429  TYPE (type_coreimpur), POINTER :: coreimpur_iter(:) !input CPO with impurities
430  TYPE (type_corefast), POINTER :: corefast_iter(:) !input CPO
431  TYPE (type_param) :: code_parameters
432 
433 
434 ! +++ Internal ETS derived types:
435  TYPE (magnetic_geometry) :: geometry !contains all geometry quantities
436  TYPE (plasma_profiles) :: profiles !contains profiles of plasma parameters
437  TYPE (transport_coefficients) :: transport !contains profiles of trasport coefficients
438  TYPE (sources_and_sinks) :: sources !contains profiles of sources
439  TYPE (time_evolution) :: evolution !contains all parameters required by time evolution
440  TYPE (run_control) :: control !contains all parameters required by run
441  TYPE (diagnostic) :: diag !contains error messages and warnings
442  TYPE (global_param) :: global !contains global
443  TYPE (impurity_profiles) :: impurity !contains profiles of impurities calculated by separate module
444 
445 
446 ! +++ Dimensions:
447  INTEGER, PARAMETER :: nocur = 1 !number of CPO ocurancies in the work flow
448  INTEGER :: nrho,irho !number of radial points (input, determined from COREPROF CPO)
449  INTEGER :: nion !number of ion species (input, determined from COREPROF CPO)
450  INTEGER :: nimp !number of impurity species (input, determined from COREIMPUR CPO)
451  INTEGER, ALLOCATABLE :: nzimp(:) !maximum number of impurity ionization states
452  INTEGER :: iimp, max_nzimp
453  INTEGER :: nneut
454  INTEGER :: nnucl
455  INTEGER, ALLOCATABLE :: ncomp(:)
456  INTEGER, ALLOCATABLE :: ntype(:)
457  integer :: j_boun
458 
459 
460 
461 ! +++ Control parameters:
462  INTEGER, INTENT(IN) :: control_integer(4) !integer control parameters
463  REAL (R8), INTENT(IN) :: control_double(6) !real control parameters
464  CHARACTER(LEN=500) :: failstring
465 
466 ! +++ Stabilization scheme !AF 25.Apr.2016, 22.Aug.2016
467  REAL (R8), DIMENSION(2) :: hyper_diff !hyper diffusivity
468 
469 ! +++ Set dimensions:
470  nrho = SIZE (coreprof_iter(1)%rho_tor)
471  CALL get_comp_dimensions(coreprof_iter(1)%COMPOSITIONS, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp)
472 
473  max_nzimp = 0
474  IF (nimp.GE.1) max_nzimp = maxval(nzimp)
475 
476  ALLOCATE (coreprof_new(1))
477  CALL copy_cpo(coreprof_iter(1),coreprof_new(1))
478 
479 
480 ! +++ Allocation of ETS derived types:
481  CALL allocate_magnetic_geometry(nrho, geometry, ifail)
482  CALL allocate_plasma_profiles(nrho,nion, profiles, ifail)
483  CALL allocate_transport_coefficients(nrho,nion, transport, ifail)
484  CALL allocate_sources_and_sinks(nrho,nion, sources, ifail)
485  CALL allocate_impurity_profiles(nrho,nimp,max_nzimp, impurity, ifail)
486  CALL allocate_global_param( global, ifail)
487  CALL allocate_time_evolution(nrho,nion, evolution, ifail)
488  CALL allocate_run_control( control, ifail)
489 
490 
491 ! +++ Copy CPOs in ETS derived types:
493  (equilibrium_old, equilibrium_iter, coreprof_old, coreprof_iter, &
494  coretransp_iter, coresource_iter, coreimpur_iter, corefast_iter, &
495  control_integer, control_double, &
496 !
497  geometry, profiles, transport, sources, impurity, evolution, &
498  control, j_boun, diag)
499 
500 ! +++ Call MAIN_PLASMA with internal ETS derived types:
501  CALL main_plasma &
502  (geometry, profiles, transport, sources, impurity, evolution, control, &
503  hyper_diff, j_boun,ifail,failstring) !AF 25.Apr.2016, 22.Aug.2016
504 ! ifail,failstring)
505 
506 ! dy check ifail and return if negative
507  if (ifail.lt.0) then
508  diag%ierr=ifail
509  diag%error_message(1:500)=failstring
510  return
511  end if
512 
513 !
514 ! TRANSPORT_EQUATIONS will substitute MAIN_PLASMA as soon as hyperdiffusion
515 ! is implemented
516 !
517 ! !! +++ Solve transport equations (update plasma parameter profiles):
518 ! CALL TRANSPORT_EQUATIONS &
519 ! (GEOMETRY, PROFILES, TRANSPORT, SOURCES, IMPURITY, &
520 ! CONTROL, DIAG)
521 
522 
523 
524 ! +++ Calculate global quantities:
525  CALL calculate_globals &
526  (geometry, profiles, sources, global, diag)
527 
528 
529 
530 ! +++ Copy ETS derived types in CPOs:
532 ! (GEOMETRY, PROFILES, TRANSPORT, SOURCES, COREPROF_NEW)
533  (geometry, profiles, transport, sources, global, coreprof_new, diag)
534 
535 
536 
537 ! +++ Deallocation of ETS derived types:
538  CALL deallocate_magnetic_geometry(geometry, ifail)
540  CALL deallocate_transport_coefficients(transport, ifail)
541  CALL deallocate_sources_and_sinks(sources, ifail)
544  CALL deallocate_run_control(control, ifail)
545 
546  IF (ALLOCATED(nzimp)) DEALLOCATE(nzimp)
547  IF (ALLOCATED(ncomp)) DEALLOCATE(ncomp)
548  IF (ALLOCATED(ntype)) DEALLOCATE(ntype)
549 
550 
551  RETURN
552 
553 
554 
555  END SUBROUTINE transport_solver_interface
556 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
557 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
558 
559 
560 END MODULE ets
561 
562 
563 
564 #ifndef NO_EUITM_ROUTINES
565 
566 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
575 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
576 
577 SUBROUTINE itmetskepler (EQUILIBRIUM_ITER,CORETRANSP,neotn,neotnp1, &
578  coreprof_old,coreprof_new,coreprof_iter, &
579  workflowtabint,workflowtabreal,code_parameters)
580 
581  USE euitm_schemas
582  USE euitm_routines
583  USE ets
584  USE ets_plasma
585 
586  IMPLICIT NONE
587 
588 
589 
590  TYPE(type_neoclassic),POINTER :: neotn(:),neotnp1(:)
591  INTEGER,DIMENSION(3) :: workflowtabint
592  REAL*8,DIMENSION(6) :: workflowtabreal
593  INTEGER :: control_integer(4)
594  REAL(R8) :: control_double(6)
595 
596 
597 
598 
599  TYPE (type_equilibrium), POINTER :: equilibrium_old(:) !input CPO with geometry quantities from previous time
600  TYPE (type_equilibrium), POINTER :: equilibrium_iter(:) !input CPO with geometry quantities from previous iteration
601  TYPE (type_coreprof), POINTER :: coreprof_old(:) !input CPO with internal ETS parameters profiles from previous time
602  TYPE (type_coreprof), POINTER :: coreprof_new(:) !input/output CPO with internal ETS parameters profiles
603  TYPE (type_coreprof), POINTER :: coreprof_iter(:) !input/output CPO with internal ETS parameters profiles from previous iteration
604  TYPE (type_coretransp), POINTER :: coretransp(:) !input CPO with transport coefficients
605  TYPE (type_coresource), POINTER :: coresource(:) !input CPO with sources
606  TYPE (type_coreimpur), POINTER :: coreimpur(:) !input CPO with impurities
607  TYPE (type_param) :: code_parameters
608  INTEGER :: nrhow,nspec,k
609 !
610 ! rename the CPO for ETS structure
611 !
612 ! EQUILIBRIUM_ITER equilibrium tn input
613 ! CORETRANSP coretransp tn input
614 ! neotn neoclassic tn input
615 ! neotnp1 neoclassic tn input
616 ! COREPROF_OLD coreprof tn input
617 ! COREPROF_NEW coreprof tnp1 input/output
618 ! COREPROF_ITER coreprof tnp1 input/output
619 ! workflowtabint
620 ! workflowtabreal
621 ! code_parameters
622 !call euitm_copy(EQUILIBRIUM_ITER,EQUILIBRIUM_OLD)
623 !
624 ! only the current diffusion equation is addressed
625 !
626 ! COREPROF_ITER=>COREPROF_NEW
627 
628  CALL euitm_copy(coreprof_new,coreprof_iter)
629  CALL euitm_copy(equilibrium_iter,equilibrium_old)
630  CALL euitm_deallocate(coreprof_new)
631 
632  nrhow=SIZE(coreprof_iter(1)%te%value)
633  nspec=SIZE(coreprof_iter(1)%ti%value,2)
634 
635  ALLOCATE(coreimpur(1))
636  ALLOCATE(coresource(1))
637 
638  IF (.NOT.ASSOCIATED(coretransp)) ALLOCATE(coretransp(1))
639  IF (.NOT.ASSOCIATED(coretransp(1)%VALUES(1)%sigma)) ALLOCATE(coretransp(1)%VALUES(1)%sigma(nrhow))
640  ALLOCATE(coresource(1)%VALUES(1)%j(nrhow),coresource(1)%VALUES(1)%sigma(nrhow))
641  coretransp(1)%VALUES(1)%sigma(:) = neotn(1)%sigma(:)
642  coresource(1)%VALUES(1)%sigma(:) = neotn(1)%sigma(:)
643  coresource(1)%VALUES(1)%j(:) = neotn(1)%jboot(:)
644 
645 !workaround for unused values
646 
647  ALLOCATE(coreprof_old(1)%vtor%value(nrhow,nspec))
648  coreprof_old(1)%vtor%value=0
649 
650  ALLOCATE(coreprof_iter(1)%ni%boundary%value(3,nspec))
651  coreprof_iter(1)%ni%boundary%value=0
652  ALLOCATE(coreprof_iter(1)%ti%boundary%value(3,nspec))
653  coreprof_iter(1)%ti%boundary%value=0
654  ALLOCATE(coreprof_iter(1)%te%boundary%value(3))
655  coreprof_iter(1)%te%boundary%value=0
656  ALLOCATE(coreprof_iter(1)%vtor%value(nrhow,nspec))
657  coreprof_iter(1)%vtor%value=0
658  ALLOCATE(coreprof_iter(1)%vtor%boundary%type(nspec))
659  coreprof_iter(1)%vtor%boundary%type=0
660  ALLOCATE(coreprof_iter(1)%vtor%boundary%value(3,nspec))
661  coreprof_iter(1)%vtor%boundary%value=0
662 
663  ALLOCATE(coretransp(1)%VALUES(1)%te_transp%diff_eff(nrhow))
664  coretransp(1)%VALUES(1)%te_transp%diff_eff=0
665  ALLOCATE(coretransp(1)%VALUES(1)%te_transp%vconv_eff(nrhow))
666  coretransp(1)%VALUES(1)%te_transp%vconv_eff=0
667  ALLOCATE(coretransp(1)%VALUES(1)%ni_transp%diff_eff(nrhow,nspec,3))
668  coretransp(1)%VALUES(1)%ni_transp%diff_eff=0
669  ALLOCATE(coretransp(1)%VALUES(1)%ni_transp%vconv_eff(nrhow,nspec,3))
670  coretransp(1)%VALUES(1)%ni_transp%vconv_eff=0
671  ALLOCATE(coretransp(1)%VALUES(1)%ti_transp%diff_eff(nrhow,nspec))
672  coretransp(1)%VALUES(1)%ti_transp%diff_eff=0
673  ALLOCATE(coretransp(1)%VALUES(1)%ti_transp%vconv_eff(nrhow,nspec))
674  coretransp(1)%VALUES(1)%ti_transp%vconv_eff=0
675  ALLOCATE(coretransp(1)%VALUES(1)%vtor_transp%diff_eff(nrhow,nspec))
676  coretransp(1)%VALUES(1)%vtor_transp%diff_eff=0
677  ALLOCATE(coretransp(1)%VALUES(1)%vtor_transp%vconv_eff(nrhow,nspec))
678  coretransp(1)%VALUES(1)%vtor_transp%vconv_eff=0
679 
680  ALLOCATE(coresource(1)%VALUES(1)%qe%exp(nrhow))
681  coresource(1)%VALUES(1)%qe%exp=0
682  ALLOCATE(coresource(1)%VALUES(1)%qe%imp(nrhow))
683  coresource(1)%VALUES(1)%qe%imp=0
684  ALLOCATE(coresource(1)%VALUES(1)%si%exp(nrhow,nspec))
685  coresource(1)%VALUES(1)%si%exp=0
686  ALLOCATE(coresource(1)%VALUES(1)%si%imp(nrhow,nspec))
687  coresource(1)%VALUES(1)%si%imp=0
688  ALLOCATE(coresource(1)%VALUES(1)%qi%exp(nrhow,nspec))
689  coresource(1)%VALUES(1)%qi%exp=0
690  ALLOCATE(coresource(1)%VALUES(1)%qi%imp(nrhow,nspec))
691  coresource(1)%VALUES(1)%qi%imp=0
692  ALLOCATE(coresource(1)%VALUES(1)%ui%exp(nrhow,nspec))
693  coresource(1)%VALUES(1)%ui%exp=0
694  ALLOCATE(coresource(1)%VALUES(1)%ui%imp(nrhow,nspec))
695  coresource(1)%VALUES(1)%ui%imp=0
696 
697  ALLOCATE(coreimpur(1)%impurity(1))
698  ALLOCATE(coreimpur(1)%IMPURITY(1)%nz(nrhow,1))
699  coreimpur(1)%IMPURITY(1)%nz=0
700  ALLOCATE(coreimpur(1)%IMPURITY(1)%flux%flux_dv(nrhow,1))
701  coreimpur(1)%IMPURITY(1)%flux%flux_dv=0
702  ALLOCATE(coreimpur(1)%IMPURITY(1)%z(nrhow,1))
703  coreimpur(1)%IMPURITY(1)%z=0
704  ALLOCATE(coreimpur(1)%IMPURITY(1)%zsq(nrhow,1))
705  coreimpur(1)%IMPURITY(1)%zsq=0
706 
707 !
708 ! actual COS parameters
709 !
710 ! workflowtabint(1) = current iteration
711 ! workflowtabint(2) = iteration maximum
712 ! workflowtabint(3) = best value
713 ! workflowtabreal(1) = error
714 ! workflowtabreal(2) = tolerance
715 ! workflowtabreal(3) = dt
716 ! workflowtabreal(4) = tn
717 ! workflowtabreal(5) = tnp1
718 ! workflowtabreal(5) = tend
719 !
720 
721 ! ---> needs to map yours own parameters (possible to add new one in the kepler framework
722 
723  control_integer(1) = 3 !solver type
724  control_integer(2) = 1 !sigma source
725  !write(*,*) "parameters of the solver",workflowtabreal
726  control_double(1) = workflowtabreal(4)
727  !CONTROL_DOUBLE(2) = 0. !amix between old and new
728  control_double(2) = 1.
729  control_double(3) = 1. !amixtr
730  control_double(4) = workflowtabreal(1)
731  control_double(5) = workflowtabreal(2)
732  control_integer(4) = 0 !j_boun parameter
733  coreprof_old(1)%psi%value = -2.0*acos(-1.0)*coreprof_old(1)%psi%value
734  coreprof_iter(1)%psi%value = -2.0*acos(-1.0)*coreprof_iter(1)%psi%value
735  CALL itm_ets(coreprof_old, coreprof_iter, coreprof_new, &
736  equilibrium_old, equilibrium_iter, &
737  coretransp, coresource, coreimpur, &
738  control_integer, control_double, code_parameters)
739  coreprof_iter(1)%psi%value=-coreprof_iter(1)%psi%value/(2.0*acos(-1.0))
740  coreprof_new(1)%psi%value=-coreprof_new(1)%psi%value/(2.0*acos(-1.0))
741  CALL euitm_deallocate(coresource)
742  CALL euitm_deallocate(coreimpur)
743 
744 END SUBROUTINE
745 
746 #endif
747 
748 
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 assign_code_parameters(codeparameters, return_status)
Definition: emeq.f90:671
subroutine allocate_magnetic_geometry(NRHO, GEOMETRY, ifail)
Definition: ets_plasma.f90:502
IMPURITY.
Definition: impurity.F90:8
Module converts to/from CPOs to ETS types.
Definition: convert.f90:8
subroutine profiles(p0, rbphi, dp0, drbphi, a)
Definition: profiles.f90:1
subroutine itm_ets(COREPROF_OLD, COREPROF_ITER, COREPROF_NEW, EQUILIBRIUM_OLD, EQUILIBRIUM_ITER, CORETRANSP, CORESOURCE, COREIMPUR, CONTROL_INTEGER, CONTROL_DOUBLE, code_parameters)
ETS.
Definition: ets.F90:25
subroutine main_plasma
Main plasma.
Definition: main_plasma.f90:16
subroutine allocate_global_param(GLOBAL, ifail)
Definition: ets_plasma.f90:630
subroutine allocate_plasma_profiles(NRHO, NION, PROFILES, ifail)
Definition: ets_plasma.f90:717
subroutine get_comp_dimensions(COMPOSITIONS, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP)
subroutine transport_solver_interface
Definition: ets.F90:378
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 allocate_sources_and_sinks(NRHO, NION, SOURCES, ifail)
Allocate profiles of sources needed by the transport solver.
subroutine allocate_run_control(CONTROL, ifail)
Allocate parameters required by the run control and iterations loop.
subroutine allocate_impurity_profiles(NRHO, NIMP, NZIMP, IMPURITY, ifail)
Allocate plasma profiles needed by the transport solver.
Module provides the interface between (external) CPO and internal ETS derived types.
Definition: ets.F90:8
subroutine deallocate_run_control(CONTROL, ifail)
Deallocate plasma profiles needed by the transport solver.
This module contains routines for allocation/deallocation if CPOs used in ETS.
subroutine allocate_transport_coefficients(NRHO, NION, TRANSPORT, ifail)
Allocate profiles of transport coefficients needed by the transport solver.
subroutine deallocate_magnetic_geometry(GEOMETRY, ifail)
Definition: ets_plasma.f90:575
subroutine deallocate_transport_coefficients(TRANSPORT, ifail)
Deallocate plasma profiles needed by the transport solver.
subroutine calculate_globals(GEOMETRY, PROFILES, SOURCES, GLOBAL, DIAG)
subroutine deallocate_sources_and_sinks(SOURCES, ifail)
Deallocate plasma profiles needed by the transport solver.
subroutine deallocate_time_evolution(EVOLUTION, ifail)
Deallocate plasma profiles needed by the transport solver.
The module declares types of variables used in ETS (transport code)
Definition: ets_plasma.f90:8
subroutine itmetskepler(EQUILIBRIUM_ITER, CORETRANSP, neotn, neotnp1, COREPROF_OLD, COREPROF_NEW, COREPROF_ITER, workflowtabint, workflowtabreal, code_parameters)
ITMETSKEPLER provides the coupling between the COS type workflow and the ETS.
Definition: ets.F90:577
subroutine deallocate_impurity_profiles(IMPURITY, ifail)
Deallocate plasma profiles needed by the transport solver.
subroutine evolution(T, R_in, R_out, El, Tr_l, Tr_U, Ip)
subroutine deallocate_plasma_profiles(PROFILES, ifail)
Deallocate plasma profiles needed by the transport solver.
Definition: ets_plasma.f90:992
subroutine allocate_time_evolution(NRHO, NION, EVOLUTION, ifail)
Allocate parameters required by time evolution.