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)
55 TYPE (type_equilibrium
),
POINTER :: equilibrium_old(:)
56 TYPE (type_equilibrium
),
POINTER :: equilibrium_iter(:)
57 TYPE (type_coreprof
),
POINTER :: coreprof_old(:)
58 TYPE (type_coreprof
),
POINTER :: coreprof_new(:)
59 TYPE (type_coreprof
),
POINTER :: coreprof_iter(:)
60 TYPE (type_coretransp
),
POINTER :: coretransp(:)
61 TYPE (type_coresource
),
POINTER :: coresource(:)
62 TYPE (type_coreimpur
),
POINTER :: coreimpur(:)
63 TYPE (type_corefast
),
POINTER :: corefast(:) => null()
64 TYPE (type_param
) :: code_parameters
65 INTEGER(ITM_I4) :: return_status
80 INTEGER,
PARAMETER :: nocur = 1
84 INTEGER,
ALLOCATABLE :: nzimp(:)
85 INTEGER :: iimp, max_nzimp
88 INTEGER :: control_integer(4)
89 REAL (R8) :: control_double(6)
93 INTEGER :: solver_type
94 INTEGER :: sigma_source
98 INTEGER :: psi_bnd_type
99 INTEGER :: ni_bnd_type
100 INTEGER :: ti_bnd_type
101 INTEGER :: te_bnd_type
102 INTEGER :: vtor_bnd_type
105 INTEGER,
SAVE :: debug_level=0
106 REAL (R8),
SAVE :: ohmic_heating_multiplier=1.0_r8
109 LOGICAL,
SAVE :: first=.true.
110 CHARACTER(LEN=500) :: failstring
114 REAL (R8),
PARAMETER,
DIMENSION(2) :: hyper_diff = (/ 0.0_r8, 0.0_r8 /)
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)
126 ALLOCATE (nzimp(nimp))
129 nzimp(iimp) = coreimpur(1)%compositions%impurities(iimp)%nzimp
132 max_nzimp = maxval(nzimp)
135 WRITE(*,*)
'Processing ets specific input'
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)
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
152 control_integer(1) = solver_type
153 control_integer(2) = sigma_source
154 control_integer(3) = quasi_neut
155 control_double(2) = amix
156 control_double(3) = amixtr
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
168 ALLOCATE (coreprof_new(1))
169 CALL copy_cpo(coreprof_iter(1),coreprof_new(1))
185 (equilibrium_old, equilibrium_iter, coreprof_old, coreprof_iter, &
186 coretransp, coresource, coreimpur, corefast, &
187 control_integer, control_double, &
190 control, j_boun, diag)
192 control%debug_level = debug_level
193 control%ohmic_heating_multiplier = ohmic_heating_multiplier
198 hyper_diff, hyper_diff, j_boun,ifail, failstring)
205 (geometry,
profiles, sources, global, diag)
212 (geometry,
profiles, transport, sources, global, coreprof_new, diag)
246 TYPE (type_param
),
INTENT(in) :: codeparameters
247 INTEGER(ikind),
INTENT(out) :: return_status
249 TYPE(tree
) :: parameter_list
250 TYPE(element
),
POINTER :: temp_pointer
251 INTEGER(ikind) :: i, nparm, n_values
252 CHARACTER(len = 132) :: cname
258 WRITE(*,*)
'Calling euitm_xml_parse'
259 CALL euitm_xml_parse(code_parameters, nparm, parameter_list)
260 WRITE(*,*)
'Called euitm_xml_parse'
264 temp_pointer => parameter_list%first
267 cname = char2str(temp_pointer%cname)
270 temp_pointer => temp_pointer%child
275 temp_pointer => temp_pointer%child
278 IF (
ALLOCATED(temp_pointer%cvalue)) &
279 CALL char2num(temp_pointer%cvalue, nrho)
281 IF (
ALLOCATED(temp_pointer%cvalue)) &
282 CALL char2num(temp_pointer%cvalue, nion)
284 IF (
ALLOCATED(temp_pointer%cvalue)) &
285 CALL char2num(temp_pointer%cvalue, nimp)
287 IF (
ALLOCATED(temp_pointer%cvalue)) &
288 CALL char2num(temp_pointer%cvalue, max_nzimp)
292 temp_pointer => temp_pointer%child
295 IF (
ALLOCATED(temp_pointer%cvalue)) &
296 CALL char2num(temp_pointer%cvalue, rhon)
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)
304 IF (
ALLOCATED(temp_pointer%cvalue)) &
305 CALL char2num(temp_pointer%cvalue, amix)
307 IF (
ALLOCATED(temp_pointer%cvalue)) &
308 CALL char2num(temp_pointer%cvalue, amixtr)
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)
318 temp_pointer => temp_pointer%child
320 CASE (
"psi_bnd_type")
321 IF (
ALLOCATED(temp_pointer%cvalue)) &
322 CALL char2num(temp_pointer%cvalue, psi_bnd_type)
324 IF (
ALLOCATED(temp_pointer%cvalue)) &
325 CALL char2num(temp_pointer%cvalue, ni_bnd_type)
327 IF (
ALLOCATED(temp_pointer%cvalue)) &
328 CALL char2num(temp_pointer%cvalue, ti_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)
338 WRITE(*, *)
'ERROR: invalid parameter', cname
343 IF (
ASSOCIATED(temp_pointer%sibling))
THEN
344 temp_pointer => temp_pointer%sibling
347 IF (
ASSOCIATED(temp_pointer%parent, parameter_list%first )) &
349 IF (
ASSOCIATED(temp_pointer%parent))
THEN
350 temp_pointer => temp_pointer%parent
352 WRITE(*, *)
'ERROR: broken list.'
359 CALL destroy_xml_tree(parameter_list)
382 (coreprof_old, coreprof_iter, coreprof_new, &
383 equilibrium_old, equilibrium_iter, &
389 control_integer, control_double, &
422 TYPE (type_equilibrium
),
POINTER :: equilibrium_old(:)
423 TYPE (type_equilibrium
),
POINTER :: equilibrium_iter(:)
424 TYPE (type_coreprof
),
POINTER :: coreprof_old(:)
425 TYPE (type_coreprof
),
POINTER :: coreprof_new(:)
426 TYPE (type_coreprof
),
POINTER :: coreprof_iter(:)
427 TYPE (type_coretransp
),
POINTER :: coretransp_iter(:)
428 TYPE (type_coresource
),
POINTER :: coresource_iter(:)
429 TYPE (type_coreimpur
),
POINTER :: coreimpur_iter(:)
430 TYPE (type_corefast
),
POINTER :: corefast_iter(:)
431 TYPE (type_param
) :: code_parameters
447 INTEGER,
PARAMETER :: nocur = 1
451 INTEGER,
ALLOCATABLE :: nzimp(:)
452 INTEGER :: iimp, max_nzimp
455 INTEGER,
ALLOCATABLE :: ncomp(:)
456 INTEGER,
ALLOCATABLE :: ntype(:)
462 INTEGER,
INTENT(IN) :: control_integer(4)
463 REAL (R8),
INTENT(IN) :: control_double(6)
464 CHARACTER(LEN=500) :: failstring
467 REAL (R8),
DIMENSION(2) :: hyper_diff
470 nrho =
SIZE (coreprof_iter(1)%rho_tor)
471 CALL
get_comp_dimensions(coreprof_iter(1)%COMPOSITIONS, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp)
474 IF (nimp.GE.1) max_nzimp = maxval(nzimp)
476 ALLOCATE (coreprof_new(1))
477 CALL copy_cpo(coreprof_iter(1),coreprof_new(1))
493 (equilibrium_old, equilibrium_iter, coreprof_old, coreprof_iter, &
494 coretransp_iter, coresource_iter, coreimpur_iter, corefast_iter, &
495 control_integer, control_double, &
498 control, j_boun, diag)
503 hyper_diff, j_boun,ifail,failstring)
509 diag%error_message(1:500)=failstring
526 (geometry,
profiles, sources, global, diag)
533 (geometry,
profiles, transport, sources, global, coreprof_new, diag)
546 IF (
ALLOCATED(nzimp))
DEALLOCATE(nzimp)
547 IF (
ALLOCATED(ncomp))
DEALLOCATE(ncomp)
548 IF (
ALLOCATED(ntype))
DEALLOCATE(ntype)
564 #ifndef NO_EUITM_ROUTINES
578 coreprof_old,coreprof_new,coreprof_iter, &
579 workflowtabint,workflowtabreal,code_parameters)
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)
599 TYPE (type_equilibrium
),
POINTER :: equilibrium_old(:)
600 TYPE (type_equilibrium
),
POINTER :: equilibrium_iter(:)
601 TYPE (type_coreprof
),
POINTER :: coreprof_old(:)
602 TYPE (type_coreprof
),
POINTER :: coreprof_new(:)
603 TYPE (type_coreprof
),
POINTER :: coreprof_iter(:)
604 TYPE (type_coretransp
),
POINTER :: coretransp(:)
605 TYPE (type_coresource
),
POINTER :: coresource(:)
606 TYPE (type_coreimpur
),
POINTER :: coreimpur(:)
607 TYPE (type_param
) :: code_parameters
608 INTEGER :: nrhow,nspec,k
628 CALL euitm_copy(coreprof_new,coreprof_iter)
629 CALL euitm_copy(equilibrium_iter,equilibrium_old)
630 CALL euitm_deallocate(coreprof_new)
632 nrhow=
SIZE(coreprof_iter(1)%te%value)
633 nspec=
SIZE(coreprof_iter(1)%ti%value,2)
635 ALLOCATE(coreimpur(1))
636 ALLOCATE(coresource(1))
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(:)
647 ALLOCATE(coreprof_old(1)%vtor%value(nrhow,nspec))
648 coreprof_old(1)%vtor%value=0
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
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
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
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
723 control_integer(1) = 3
724 control_integer(2) = 1
726 control_double(1) = workflowtabreal(4)
728 control_double(2) = 1.
729 control_double(3) = 1.
730 control_double(4) = workflowtabreal(1)
731 control_double(5) = workflowtabreal(2)
732 control_integer(4) = 0
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)
subroutine convert_cpo_to_internal_types(EQUILIBRIUM_OLD, EQUILIBRIUM_ITER, COREPROF_OLD, COREPROF_ITER,CORETRANSP, CORESOURCE, COREIMPUR, COREFAST,CONTROL_INTEGER, CONTROL_DOUBLE,
subroutine assign_code_parameters(codeparameters, return_status)
subroutine allocate_magnetic_geometry(NRHO, GEOMETRY, ifail)
Module converts to/from CPOs to ETS types.
subroutine profiles(p0, rbphi, dp0, drbphi, a)
subroutine itm_ets(COREPROF_OLD, COREPROF_ITER, COREPROF_NEW, EQUILIBRIUM_OLD, EQUILIBRIUM_ITER, CORETRANSP, CORESOURCE, COREIMPUR, CONTROL_INTEGER, CONTROL_DOUBLE, code_parameters)
ETS.
subroutine main_plasma
Main plasma.
subroutine allocate_global_param(GLOBAL, ifail)
subroutine allocate_plasma_profiles(NRHO, NION, PROFILES, ifail)
subroutine get_comp_dimensions(COMPOSITIONS, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP)
subroutine transport_solver_interface
subroutine convert_internal_to_cpo_types(GEOMETRY, PROFILES, TRANSPORT, SOURCES, GLOBAL, COREPROF, DIAG)
This routine converts ETS into the CPOs derived types.
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.
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)
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)
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.
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.
subroutine allocate_time_evolution(NRHO, NION, EVOLUTION, ifail)
Allocate parameters required by time evolution.