22 npsi, nrho, neq_dim1, neq_dim2, max_npoints, &
24 nnucl, nion, nimp, nzimp, nneut, ncomp, ntype, &
28 amn, zn, zion, amn_imp, zn_imp, max_z_imp, &
30 cold_neutrals, thermal_neutrals, &
31 fast_neutrals, nbi_neutrals, &
34 psi_type, ne_type, ni_type, te_type, ti_type, &
35 vtor_type,imp_type,n0_type, t0_type, &
37 psi_value, ne_value, ni_value, te_value, ti_value, &
38 vtor_value, imp_value, n0_value, t0_value, &
40 shot_in, run_in, interpol, db_in, &
41 shot_out, run_out, tau_out, db_out, &
42 solver_type, sigma_source, tau, amix, convrec, &
45 ip, geo_ax, plasma_ax, amin, elong, tria_up, tria_low, &
47 prof_flag, j0_flag, q0_flag, eq_source, &
48 time_dep_input, ext_equil, equil_mod, &
49 ext_source, ext_transport, add_transport, quasi_neut, &
50 tau_inc, tau_dec, iter_inc, iter_dec, &
52 exp_option, exp_ncols, &
53 evolution_labels, evolution_data, &
54 augment_equil, rho_f, icoronal, &
67 INTEGER :: neq_max_npoints
68 INTEGER :: max_npoints
74 INTEGER,
ALLOCATABLE :: nzimp(:)
76 INTEGER,
ALLOCATABLE :: ncomp(:)
77 INTEGER,
ALLOCATABLE :: ntype(:)
87 INTEGER :: solver_type
88 INTEGER :: sigma_source
93 REAL (R8) :: start_time
105 REAL (R8),
ALLOCATABLE :: amn(:)
106 REAL (R8),
ALLOCATABLE :: zn(:)
107 REAL (R8),
ALLOCATABLE :: zion(:)
108 REAL (R8),
ALLOCATABLE :: amn_imp(:)
109 REAL (R8),
ALLOCATABLE :: zn_imp(:)
110 REAL (R8),
ALLOCATABLE :: max_z_imp(:)
112 INTEGER :: cold_neutrals
113 INTEGER :: thermal_neutrals
114 INTEGER :: fast_neutrals
115 INTEGER :: nbi_neutrals
117 INTEGER :: psi_bnd_type
118 INTEGER :: ne_bnd_type
119 INTEGER :: ni_bnd_type
120 INTEGER :: ti_bnd_type
121 INTEGER :: te_bnd_type
122 INTEGER :: vtor_bnd_type
123 INTEGER :: nimp_bnd_type
124 INTEGER :: n0_bnd_type
125 INTEGER :: t0_bnd_type
127 REAL (R8) :: psi_bnd_value
128 REAL (R8) :: ne_bnd_value
129 REAL (R8),
ALLOCATABLE :: ni_bnd_value(:)
130 REAL (R8),
ALLOCATABLE :: ti_bnd_value(:)
131 REAL (R8) :: te_bnd_value
132 REAL (R8),
ALLOCATABLE :: vtor_bnd_value(:)
133 REAL (R8),
ALLOCATABLE :: nimp_bnd_value(:,:)
134 REAL (R8),
ALLOCATABLE :: n0_bnd_value_cold(:)
135 REAL (R8),
ALLOCATABLE :: n0_bnd_value_thermal(:)
136 REAL (R8),
ALLOCATABLE :: t0_bnd_value_cold(:)
137 REAL (R8),
ALLOCATABLE :: t0_bnd_value_thermal(:)
141 REAL (R8) :: psi_value(3)
143 REAL (R8) :: ne_value(3)
145 REAL (R8) :: te_value(3)
146 INTEGER,
ALLOCATABLE :: ni_type(:)
147 REAL (R8),
ALLOCATABLE :: ni_value(:,:)
148 INTEGER,
ALLOCATABLE :: ti_type(:)
149 REAL (R8),
ALLOCATABLE :: ti_value(:,:)
150 INTEGER,
ALLOCATABLE :: vtor_type(:)
151 REAL (R8),
ALLOCATABLE :: vtor_value(:,:)
153 INTEGER,
ALLOCATABLE :: imp_type(:,:)
154 REAL (R8),
ALLOCATABLE :: imp_value(:,:,:)
156 INTEGER,
ALLOCATABLE :: n0_type(:,:)
157 REAL (R8),
ALLOCATABLE :: n0_value(:,:,:)
158 INTEGER,
ALLOCATABLE :: t0_type(:,:)
159 REAL (R8),
ALLOCATABLE :: t0_value(:,:,:)
163 REAL (R8) :: geo_ax(3)
164 REAL (R8) :: plasma_ax(3)
165 REAL (R8) :: r_geo, z_geo, b_geo
166 REAL (R8) :: r_plasma, z_plasma, b_plasma
170 REAL (R8) :: tria_low
177 INTEGER :: shot_in, run_in
179 INTEGER :: time_dep_input
182 INTEGER :: augment_equil
183 INTEGER :: ext_source
184 INTEGER :: ext_transport
185 REAL (R8) :: add_transport
186 INTEGER :: shot_out, run_out
188 INTEGER :: exp_option
190 character (len=32) :: db_in, db_out
191 INTEGER,
PARAMETER :: buflen = 256
192 CHARACTER(len=BUFLEN) :: rho_f
194 CHARACTER (len=32) :: tmp_labels(100)
195 REAL (R8) :: tmp_data(100*1000)
197 CHARACTER (len=32),
POINTER :: evolution_labels(:)
198 REAL (R8),
POINTER :: evolution_data(:,:)
200 INTEGER :: return_status, n_labels, n_data, n_rows
201 TYPE (type_param
) :: code_parameters
223 neq_max_npoints = 100
256 add_transport = 0.0_r8
274 nzimp, ncomp, ntype, max_npoints, &
276 amn, zn, zion, amn_imp, zn_imp, max_z_imp, &
278 ni_bnd_value, ti_bnd_value, vtor_bnd_value, nimp_bnd_value, &
280 n0_bnd_value_cold, n0_bnd_value_thermal, &
282 t0_bnd_value_cold, t0_bnd_value_thermal)
284 if(
allocated(nzimp))
then
285 write(*,*)
'process_xml: nzimp allocated'
286 write(*,*)
'nzimp = ', nzimp
288 write(*,*)
'process_xml: nzimp not allocated'
292 ALLOCATE (ni_type(nion))
293 ALLOCATE (ti_type(nion))
294 ALLOCATE (vtor_type(nion))
296 ALLOCATE (ni_value(3,nion))
297 ALLOCATE (ti_value(3,nion))
298 ALLOCATE (vtor_value(3,nion))
301 ALLOCATE (imp_type(nimp,maxval(nzimp)))
302 ALLOCATE (imp_value(nimp,3,maxval(nzimp)))
305 write(*,*)
'NNEUT = ', nneut
307 ALLOCATE (n0_type(nneut,maxval(ntype)))
308 ALLOCATE (n0_value(nneut,3,maxval(ntype)))
309 ALLOCATE (t0_type(nneut,maxval(ntype)))
310 ALLOCATE (t0_value(nneut,3,maxval(ntype)))
314 psi_type = psi_bnd_type
316 psi_value(1) = psi_bnd_value
317 ne_type = ne_bnd_type
319 ne_value(1) = ne_bnd_value
320 te_type = te_bnd_type
322 te_value(1) = te_bnd_value
323 ni_type(:) = ni_bnd_type
325 ni_value(1,:) = ni_bnd_value(:)
326 ti_type(:) = ti_bnd_type
328 ti_value(1,:) = te_bnd_value
329 vtor_type(:) = vtor_bnd_type
331 vtor_value(1,:) = vtor_bnd_value(:)
334 imp_type(:,:) = nimp_bnd_type
337 DO izimp = 1, nzimp(iimp)
338 imp_value(iimp,1,izimp)= nimp_bnd_value(iimp,izimp)
344 n0_type(:,:) = n0_bnd_type
345 t0_type(:,:) = t0_bnd_type
348 n0_value(:,1,1) = n0_bnd_value_cold(:)
349 n0_value(:,1,2) = n0_bnd_value_thermal(:)
350 t0_value(:,1,1) = t0_bnd_value_cold(:)
351 t0_value(:,1,2) = t0_bnd_value_thermal(:)
357 IF(tau_out .LT. 0.0_r8) tau_out = 0.1_r8
359 IF (return_status /= 0)
THEN
360 WRITE(*, *)
'ERROR: Could not assign code parameters.'
375 nzimp, ncomp, ntype, max_npoints, &
377 amn, zn, zion, amn_imp, zn_imp, max_z_imp, &
379 ni_bnd_value, ti_bnd_value, vtor_bnd_value, nimp_bnd_value, &
381 n0_bnd_value_cold, n0_bnd_value_thermal, &
383 t0_bnd_value_cold, t0_bnd_value_thermal)
395 TYPE (type_param
),
INTENT(in) :: codeparameters
396 INTEGER(ikind),
INTENT(out) :: return_status
398 TYPE(tree
) :: parameter_list
399 TYPE(element
),
POINTER :: temp_pointer
400 INTEGER(ikind) :: i, nparm, n_values, n_data
401 INTEGER :: n_data1, n_data2, n_data3
402 CHARACTER(len = 132) :: cname
403 INTEGER :: integer_data(1000)
404 REAL(R8) :: real_data(1000)
405 INTEGER :: idata, nn, iimp, izimp
407 INTEGER,
ALLOCATABLE :: nzimp(:)
408 INTEGER,
ALLOCATABLE :: ncomp(:)
409 INTEGER,
ALLOCATABLE :: ntype(:)
410 INTEGER :: max_npoints
412 REAL (R8),
ALLOCATABLE :: amn(:)
413 REAL (R8),
ALLOCATABLE :: zn(:)
414 REAL (R8),
ALLOCATABLE :: zion(:)
415 REAL (R8),
ALLOCATABLE :: amn_imp(:)
416 REAL (R8),
ALLOCATABLE :: zn_imp(:)
417 REAL (R8),
ALLOCATABLE :: max_z_imp(:)
419 REAL (R8),
ALLOCATABLE :: ni_bnd_value(:)
420 REAL (R8),
ALLOCATABLE :: ti_bnd_value(:)
421 REAL (R8),
ALLOCATABLE :: vtor_bnd_value(:)
422 REAL (R8),
ALLOCATABLE :: nimp_bnd_value(:,:)
423 REAL (R8),
ALLOCATABLE :: n0_bnd_value_cold(:)
424 REAL (R8),
ALLOCATABLE :: n0_bnd_value_thermal(:)
425 REAL (R8),
ALLOCATABLE :: t0_bnd_value_cold(:)
426 REAL (R8),
ALLOCATABLE :: t0_bnd_value_thermal(:)
432 WRITE(*,*)
'Calling euitm_xml_parse'
433 CALL euitm_xml_parse(code_parameters, nparm, parameter_list)
434 WRITE(*,*)
'Called euitm_xml_parse'
438 temp_pointer => parameter_list%first
441 cname = char2str(temp_pointer%cname)
444 temp_pointer => temp_pointer%child
449 temp_pointer => temp_pointer%child
452 IF (
ALLOCATED(temp_pointer%cvalue)) &
453 CALL char2num(temp_pointer%cvalue, shot_in)
455 IF (
ALLOCATED(temp_pointer%cvalue)) &
456 CALL char2num(temp_pointer%cvalue, run_in)
458 IF (
ALLOCATED(temp_pointer%cvalue)) &
459 CALL char2num(temp_pointer%cvalue, interpol)
460 CASE (
"time_dep_input")
461 IF (
ALLOCATED(temp_pointer%cvalue)) &
462 CALL char2num(temp_pointer%cvalue, time_dep_input)
464 if (
allocated(temp_pointer%cvalue)) &
465 db_in = char2str(temp_pointer%cvalue)
470 temp_pointer => temp_pointer%child
473 IF (
ALLOCATED(temp_pointer%cvalue)) &
474 CALL char2num(temp_pointer%cvalue, shot_out)
476 IF (
ALLOCATED(temp_pointer%cvalue)) &
477 CALL char2num(temp_pointer%cvalue, run_out)
479 IF (
ALLOCATED(temp_pointer%cvalue)) &
480 CALL char2num(temp_pointer%cvalue, tau_out)
482 if (
allocated(temp_pointer%cvalue)) &
483 db_out = char2str(temp_pointer%cvalue)
489 temp_pointer => temp_pointer%child
492 IF (
ALLOCATED(temp_pointer%cvalue)) &
493 rho_f = char2str(temp_pointer%cvalue)
495 IF (
ALLOCATED(temp_pointer%cvalue)) &
496 CALL char2num(temp_pointer%cvalue, solver_type)
497 CASE (
"sigma_source")
498 IF (
ALLOCATED(temp_pointer%cvalue)) &
499 CALL char2num(temp_pointer%cvalue, sigma_source)
501 IF (
ALLOCATED(temp_pointer%cvalue)) &
502 CALL char2num(temp_pointer%cvalue, tau)
504 IF (
ALLOCATED(temp_pointer%cvalue)) &
505 CALL char2num(temp_pointer%cvalue, tau_inc)
507 IF (
ALLOCATED(temp_pointer%cvalue)) &
508 CALL char2num(temp_pointer%cvalue, tau_dec)
510 IF (
ALLOCATED(temp_pointer%cvalue)) &
511 CALL char2num(temp_pointer%cvalue, iter_inc)
513 IF (
ALLOCATED(temp_pointer%cvalue)) &
514 CALL char2num(temp_pointer%cvalue, iter_dec)
516 IF (
ALLOCATED(temp_pointer%cvalue)) &
517 CALL char2num(temp_pointer%cvalue, tau_min)
519 IF (
ALLOCATED(temp_pointer%cvalue)) &
520 CALL char2num(temp_pointer%cvalue, tau_max)
522 IF (
ALLOCATED(temp_pointer%cvalue)) &
523 CALL char2num(temp_pointer%cvalue, amix)
525 IF (
ALLOCATED(temp_pointer%cvalue)) &
526 CALL char2num(temp_pointer%cvalue, convrec)
528 IF (
ALLOCATED(temp_pointer%cvalue)) &
529 CALL char2num(temp_pointer%cvalue, ntime)
531 IF (
ALLOCATED(temp_pointer%cvalue)) &
532 CALL char2num(temp_pointer%cvalue, start_time)
534 IF (
ALLOCATED(temp_pointer%cvalue)) &
535 CALL char2num(temp_pointer%cvalue, nsol)
537 IF (
ALLOCATED(temp_pointer%cvalue)) &
538 CALL char2num(temp_pointer%cvalue, ext_equil)
540 if (
allocated(temp_pointer%cvalue)) &
541 call char2num(temp_pointer%cvalue, equil_mod)
542 CASE (
"augment_equil")
543 IF (
ALLOCATED(temp_pointer%cvalue)) &
544 CALL char2num(temp_pointer%cvalue, augment_equil)
546 IF (
ALLOCATED(temp_pointer%cvalue)) &
547 CALL char2num(temp_pointer%cvalue, ext_source)
548 CASE (
"ext_transport")
549 IF (
ALLOCATED(temp_pointer%cvalue)) &
550 CALL char2num(temp_pointer%cvalue, ext_transport)
551 CASE (
"add_transport")
552 IF (
ALLOCATED(temp_pointer%cvalue)) &
553 CALL char2num(temp_pointer%cvalue, add_transport)
555 IF (
ALLOCATED(temp_pointer%cvalue)) &
556 CALL char2num(temp_pointer%cvalue, quasi_neut)
558 IF (
ALLOCATED(temp_pointer%cvalue)) &
559 CALL char2num(temp_pointer%cvalue, icoronal)
563 temp_pointer => temp_pointer%child
566 IF (
ALLOCATED(temp_pointer%cvalue)) &
567 CALL char2num(temp_pointer%cvalue, prof_flag)
569 IF (
ALLOCATED(temp_pointer%cvalue)) &
570 CALL char2num(temp_pointer%cvalue, j0_flag)
572 IF (
ALLOCATED(temp_pointer%cvalue)) &
573 CALL char2num(temp_pointer%cvalue, q0_flag)
578 temp_pointer => temp_pointer%child
581 IF (
ALLOCATED(temp_pointer%cvalue)) &
582 CALL char2num(temp_pointer%cvalue, npsi)
584 IF (
ALLOCATED(temp_pointer%cvalue)) &
585 CALL char2num(temp_pointer%cvalue, neq_dim1)
587 IF (
ALLOCATED(temp_pointer%cvalue)) &
588 CALL char2num(temp_pointer%cvalue, neq_dim2)
589 CASE (
"neq_max_npoints")
590 IF (
ALLOCATED(temp_pointer%cvalue)) &
591 CALL char2num(temp_pointer%cvalue, max_npoints)
593 IF (
ALLOCATED(temp_pointer%cvalue)) &
594 CALL char2num(temp_pointer%cvalue, nrho)
600 temp_pointer => temp_pointer%child
603 IF (
ALLOCATED(temp_pointer%cvalue)) &
604 CALL char2num(temp_pointer%cvalue, ip)
606 IF (
ALLOCATED(temp_pointer%cvalue)) &
607 CALL char2num(temp_pointer%cvalue, r_geo)
609 IF (
ALLOCATED(temp_pointer%cvalue)) &
610 CALL char2num(temp_pointer%cvalue, z_geo)
612 IF (
ALLOCATED(temp_pointer%cvalue)) &
613 CALL char2num(temp_pointer%cvalue, b_geo)
615 IF (
ALLOCATED(temp_pointer%cvalue)) &
616 CALL char2num(temp_pointer%cvalue, r_plasma)
618 IF (
ALLOCATED(temp_pointer%cvalue)) &
619 CALL char2num(temp_pointer%cvalue, z_plasma)
621 IF (
ALLOCATED(temp_pointer%cvalue)) &
622 CALL char2num(temp_pointer%cvalue, b_plasma)
624 IF (
ALLOCATED(temp_pointer%cvalue)) &
625 CALL char2num(temp_pointer%cvalue, amin)
627 IF (
ALLOCATED(temp_pointer%cvalue)) &
628 CALL char2num(temp_pointer%cvalue, elong)
630 IF (
ALLOCATED(temp_pointer%cvalue)) &
631 CALL char2num(temp_pointer%cvalue, tria_up)
633 IF (
ALLOCATED(temp_pointer%cvalue)) &
634 CALL char2num(temp_pointer%cvalue, tria_low)
636 IF (
ALLOCATED(temp_pointer%cvalue)) &
637 CALL char2num(temp_pointer%cvalue, eq_source)
643 plasma_ax(1) = r_plasma
644 plasma_ax(2) = z_plasma
645 plasma_ax(3) = b_plasma
648 CASE (
"compositions")
649 temp_pointer => temp_pointer%child
652 temp_pointer => temp_pointer%child
655 IF (
ALLOCATED(temp_pointer%cvalue)) &
656 CALL scan_str2real(char2str(temp_pointer%cvalue), real_data, n_data1)
657 ALLOCATE(amn(n_data1))
658 amn = real_data(1:n_data1)
661 IF (
ALLOCATED(temp_pointer%cvalue)) &
662 CALL scan_str2real(char2str(temp_pointer%cvalue), real_data, n_data2)
663 ALLOCATE(zn(n_data2))
664 zn = real_data(1:n_data2)
667 IF (
ALLOCATED(temp_pointer%cvalue)) &
668 CALL scan_str2real(char2str(temp_pointer%cvalue), real_data, n_data3)
669 ALLOCATE(zion(n_data3))
670 zion = real_data(1:n_data3)
673 nion = min(n_data1, n_data2, n_data3)
676 temp_pointer => temp_pointer%child
679 IF (
ALLOCATED(temp_pointer%cvalue))
then
680 CALL scan_str2real(char2str(temp_pointer%cvalue), real_data, n_data1)
681 ALLOCATE(amn_imp(n_data1))
682 amn_imp = real_data(1:n_data1)
688 IF (
ALLOCATED(temp_pointer%cvalue))
then
689 CALL scan_str2real(char2str(temp_pointer%cvalue), real_data, n_data2)
690 ALLOCATE(zn_imp(n_data2))
691 zn_imp = real_data(1:n_data2)
697 IF (
ALLOCATED(temp_pointer%cvalue))
then
698 CALL scan_str2real(char2str(temp_pointer%cvalue), real_data, n_data3)
699 ALLOCATE(max_z_imp(n_data3))
700 max_z_imp = real_data(1:n_data3)
705 nimp = min(n_data1, n_data2, n_data3)
707 ALLOCATE (nzimp(nimp))
708 nzimp = nint(max_z_imp)
712 temp_pointer => temp_pointer%child
714 CASE (
"cold_neutrals")
715 IF (
ALLOCATED(temp_pointer%cvalue)) &
716 CALL char2num(temp_pointer%cvalue, cold_neutrals)
717 IF (cold_neutrals.gt.0) cold_neutrals = 1
718 CASE (
"thermal_neutrals")
719 IF (
ALLOCATED(temp_pointer%cvalue)) &
720 CALL char2num(temp_pointer%cvalue, thermal_neutrals)
721 IF (thermal_neutrals.gt.0) thermal_neutrals = 1
722 CASE (
"fast_neutrals")
723 IF (
ALLOCATED(temp_pointer%cvalue)) &
724 CALL char2num(temp_pointer%cvalue, fast_neutrals)
725 IF (fast_neutrals.gt.0) fast_neutrals = 1
726 CASE (
"NBI_neutrals")
727 IF (
ALLOCATED(temp_pointer%cvalue)) &
728 CALL char2num(temp_pointer%cvalue, nbi_neutrals)
729 IF (nbi_neutrals.gt.0) nbi_neutrals = 1
736 if(cold_neutrals + thermal_neutrals + fast_neutrals + nbi_neutrals.eq.0)
then
740 ALLOCATE (ncomp(nneut))
741 ALLOCATE (ntype(nneut))
743 ntype = cold_neutrals + thermal_neutrals + fast_neutrals + nbi_neutrals
745 ALLOCATE (ni_bnd_value(nion))
746 ALLOCATE (ti_bnd_value(nion))
747 ALLOCATE (vtor_bnd_value(nion))
748 if(nimp .gt. 0)
ALLOCATE (nimp_bnd_value(nimp,maxval(nzimp)))
749 ALLOCATE (n0_bnd_value_cold(nneut))
750 ALLOCATE (n0_bnd_value_thermal(nneut))
751 ALLOCATE (t0_bnd_value_cold(nneut))
752 ALLOCATE (t0_bnd_value_thermal(nneut))
758 temp_pointer => temp_pointer%child
761 temp_pointer => temp_pointer%child
763 CASE (
"psi_bnd_type")
764 IF (
ALLOCATED(temp_pointer%cvalue)) &
765 CALL char2num(temp_pointer%cvalue, psi_bnd_type)
767 IF (
ALLOCATED(temp_pointer%cvalue)) &
768 CALL char2num(temp_pointer%cvalue, ne_bnd_type)
770 IF (
ALLOCATED(temp_pointer%cvalue)) &
771 CALL char2num(temp_pointer%cvalue, ni_bnd_type)
773 IF (
ALLOCATED(temp_pointer%cvalue)) &
774 CALL char2num(temp_pointer%cvalue, ti_bnd_type)
776 IF (
ALLOCATED(temp_pointer%cvalue)) &
777 CALL char2num(temp_pointer%cvalue, te_bnd_type)
778 CASE (
"vtor_bnd_type")
779 IF (
ALLOCATED(temp_pointer%cvalue)) &
780 CALL char2num(temp_pointer%cvalue, vtor_bnd_type)
781 CASE (
"nimp_bnd_type")
782 IF (
ALLOCATED(temp_pointer%cvalue)) &
783 CALL char2num(temp_pointer%cvalue, nimp_bnd_type)
785 IF (
ALLOCATED(temp_pointer%cvalue)) &
786 CALL char2num(temp_pointer%cvalue, n0_bnd_type)
788 IF (
ALLOCATED(temp_pointer%cvalue)) &
789 CALL char2num(temp_pointer%cvalue, t0_bnd_type)
794 temp_pointer => temp_pointer%child
796 CASE (
"psi_bnd_value")
797 IF (
ALLOCATED(temp_pointer%cvalue)) &
798 CALL char2num(temp_pointer%cvalue, psi_bnd_value)
799 CASE (
"ne_bnd_value")
800 IF (
ALLOCATED(temp_pointer%cvalue)) &
801 CALL char2num(temp_pointer%cvalue, ne_bnd_value)
802 CASE (
"ni_bnd_value")
803 IF (
ALLOCATED(temp_pointer%cvalue)) &
804 CALL scan_str2real(char2str(temp_pointer%cvalue), real_data, n_data)
805 ni_bnd_value = real_data(1:n_data)
807 CASE (
"ti_bnd_value")
808 IF (
ALLOCATED(temp_pointer%cvalue)) &
809 CALL scan_str2real(char2str(temp_pointer%cvalue), real_data, n_data)
810 ti_bnd_value = real_data(1:n_data)
812 CASE (
"te_bnd_value")
813 IF (
ALLOCATED(temp_pointer%cvalue)) &
814 CALL char2num(temp_pointer%cvalue, te_bnd_value)
815 CASE (
"vtor_bnd_value")
816 IF (
ALLOCATED(temp_pointer%cvalue)) &
817 CALL scan_str2real(char2str(temp_pointer%cvalue), real_data, n_data)
818 vtor_bnd_value = real_data(1:n_data)
820 CASE (
"nimp_bnd_value")
821 IF (
ALLOCATED(temp_pointer%cvalue))
then
822 CALL scan_str2real(char2str(temp_pointer%cvalue), real_data, n_data)
823 nimp_bnd_value = 0.0_r8
827 DO izimp = 1, nzimp(iimp)
828 IF ((nn+izimp).LE.n_data) &
829 nimp_bnd_value(iimp,izimp) = real_data(nn+izimp)
831 nn = nn + nzimp(iimp)
842 CASE (
"n0_bnd_value_cold")
843 IF (
ALLOCATED(temp_pointer%cvalue)) &
844 CALL scan_str2real(char2str(temp_pointer%cvalue), real_data, n_data)
845 n0_bnd_value_cold = real_data(1:n_data)
847 CASE (
"n0_bnd_value_thermal")
848 IF (
ALLOCATED(temp_pointer%cvalue)) &
849 CALL scan_str2real(char2str(temp_pointer%cvalue), real_data, n_data)
850 n0_bnd_value_thermal = real_data(1:n_data)
852 CASE (
"t0_bnd_value_cold")
853 IF (
ALLOCATED(temp_pointer%cvalue)) &
854 CALL scan_str2real(char2str(temp_pointer%cvalue), real_data, n_data)
855 t0_bnd_value_cold = real_data(1:n_data)
857 CASE (
"t0_bnd_value_thermal")
858 IF (
ALLOCATED(temp_pointer%cvalue)) &
859 CALL scan_str2real(char2str(temp_pointer%cvalue), real_data, n_data)
860 t0_bnd_value_thermal = real_data(1:n_data)
865 CASE (
"experimental")
866 temp_pointer => temp_pointer%child
869 IF (
ALLOCATED(temp_pointer%cvalue)) &
870 CALL char2num(temp_pointer%cvalue, exp_option)
872 IF (
ALLOCATED(temp_pointer%cvalue)) &
873 CALL char2num(temp_pointer%cvalue, exp_ncols)
874 CASE (
"evolution_labels")
875 IF (
ALLOCATED(temp_pointer%cvalue))
THEN
876 CALL scan_str2str(char2str(temp_pointer%cvalue), 32, tmp_labels, n_labels)
877 ALLOCATE(evolution_labels(n_labels))
878 evolution_labels=tmp_labels(1:n_labels)
880 CASE (
"evolution_data")
881 IF (
ALLOCATED(temp_pointer%cvalue))
THEN
882 CALL scan_str2real(char2str(temp_pointer%cvalue), tmp_data, n_data)
883 IF(exp_ncols.LE.0)
THEN
884 WRITE(*,*)
'exp_ncols = ', exp_ncols,
' invalid'
885 stop
'Error in exp_ncols'
887 n_rows=n_data/exp_ncols
888 IF(n_rows*exp_ncols .NE. n_data)
THEN
889 WRITE(*,*)
'Mismatch in "evolution_data" length: ', n_rows, exp_ncols, n_data
890 stop
'Error in "evolution_data" length'
892 ALLOCATE(evolution_data(exp_ncols, n_rows))
893 evolution_data=reshape(tmp_data(1:n_data),(/ exp_ncols, n_rows /))
899 WRITE(*, *)
'ERROR: invalid parameter', cname
904 IF (
ASSOCIATED(temp_pointer%sibling))
THEN
905 temp_pointer => temp_pointer%sibling
908 IF (
ASSOCIATED(temp_pointer%parent, parameter_list%first )) &
910 IF (
ASSOCIATED(temp_pointer%parent))
THEN
911 temp_pointer => temp_pointer%parent
913 WRITE(*, *)
'ERROR: broken list.'
920 CALL destroy_xml_tree(parameter_list)
922 if(
allocated(nzimp))
then
923 write(*,*)
'assign_code_parameters: nzimp allocated'
924 write(*,*)
'nzimp = ', nzimp
926 write(*,*)
'assign_code_parameters: nzimp not allocated'
941 INTEGER n_lines, in_xml, ios, i
942 CHARACTER (len=*) :: filename
943 TYPE (type_codeparam
) :: codeparam
944 CHARACTER(len = 132) :: xml_line
946 OPEN (unit = in_xml, file = filename, status =
'old', &
947 action =
'read', iostat = ios)
950 WRITE(*,*)
'Could not open ',trim(filename)
951 stop
' ERROR: XML file does not exist '
957 READ (in_xml,
'(a)', iostat = ios) xml_line
959 n_lines = n_lines + 1
967 ALLOCATE(codeparam%codename(1))
968 codeparam%codename(1)=
'ETS'
969 ALLOCATE(codeparam%codeversion(1))
970 codeparam%codeversion(1)=version
971 WRITE(*,*)
'Code = ',trim(codeparam%codename(1)),
' version = ',trim(codeparam%codeversion(1))
972 ALLOCATE(codeparam%parameters(n_lines))
974 READ (in_xml,
'(a)', iostat = ios) codeparam%parameters(i)
1002 TYPE (type_coreprof
),
POINTER :: coreprof(:)
1005 INTEGER :: irho,iion,itime
1006 INTEGER :: nrho,nion
1008 CHARACTER (33) filename
1010 nrho =
SIZE(coreprof(1)%rho_tor)
1011 nion =
SIZE(coreprof(1)%compositions%ions)
1013 WRITE(filename,
'(a,i7.7,a)')
'eq_ets_data/OUTPUT/OUT',itime,
'.DAT'
1015 OPEN (unit=10, file=filename)
1021 WRITE (10,
'(10(1x,e16.8))') coreprof(1)%rho_tor(irho), &
1023 coreprof(1)%ni%value(irho,nion), &
1025 coreprof(1)%ne%value(irho), &
1027 coreprof(1)%ti%value(irho,nion), &
1029 coreprof(1)%te%value(irho), &
1031 coreprof(1)%vtor%value(irho,nion), &
1033 coreprof(1)%psi%value(irho), &
1035 coreprof(1)%profiles1d%jtot%value(irho), &
1037 coreprof(1)%profiles1d%q%value(irho), &
1039 coreprof(1)%profiles1d%zeff%value(irho)
1068 TYPE (type_equilibrium
),
POINTER :: equilibrium(:)
1071 INTEGER :: irho,itime
1074 CHARACTER (35) filename
1076 nrho =
SIZE(equilibrium(1)%profiles_1d%rho_tor)
1077 WRITE(*,*)
"ITIME=",itime
1079 WRITE(filename,
'(a,i7.7,a)')
'eq_ets_data/OUTPUT/EQOUT',itime,
'.DAT'
1081 OPEN (unit=10, file=filename)
1083 WRITE(*,*)
ASSOCIATED(equilibrium(1)%profiles_1d%rho_tor), &
1084 ASSOCIATED(equilibrium(1)%profiles_1d%q), &
1085 ASSOCIATED(equilibrium(1)%profiles_1d%pressure), &
1086 ASSOCIATED(equilibrium(1)%profiles_1d%jparallel), &
1087 ASSOCIATED(equilibrium(1)%profiles_1d%gm1), &
1088 ASSOCIATED(equilibrium(1)%profiles_1d%gm2), &
1089 ASSOCIATED(equilibrium(1)%profiles_1d%gm3), &
1090 ASSOCIATED(equilibrium(1)%profiles_1d%gm4), &
1091 ASSOCIATED(equilibrium(1)%profiles_1d%gm5), &
1092 ASSOCIATED(equilibrium(1)%profiles_1d%gm6), &
1093 ASSOCIATED(equilibrium(1)%profiles_1d%gm7), &
1094 ASSOCIATED(equilibrium(1)%profiles_1d%volume), &
1095 ASSOCIATED(equilibrium(1)%profiles_1d%vprime), &
1096 ASSOCIATED(equilibrium(1)%profiles_1d%area), &
1097 ASSOCIATED(equilibrium(1)%profiles_1d%aprime), &
1098 ASSOCIATED(equilibrium(1)%profiles_1d%F_dia)
1102 WRITE (10,
'(16(1x,e16.8))') equilibrium(1)%profiles_1d%rho_tor(irho), &
1104 equilibrium(1)%profiles_1d%q(irho), equilibrium(1)%profiles_1d%pressure(irho), &
1106 equilibrium(1)%profiles_1d%jparallel(irho), equilibrium(1)%profiles_1d%gm1(irho), &
1108 equilibrium(1)%profiles_1d%gm2(irho), equilibrium(1)%profiles_1d%gm3(irho), &
1110 equilibrium(1)%profiles_1d%gm4(irho), equilibrium(1)%profiles_1d%gm5(irho), &
1112 equilibrium(1)%profiles_1d%gm6(irho), equilibrium(1)%profiles_1d%gm7(irho), &
1114 equilibrium(1)%profiles_1d%volume(irho), equilibrium(1)%profiles_1d%vprime(irho), &
1116 equilibrium(1)%profiles_1d%area(irho), equilibrium(1)%profiles_1d%aprime(irho), &
1118 equilibrium(1)%profiles_1d%F_dia(irho)
subroutine process_xml(SOLVER_TYPE, SIGMA_SOURCE, TAU, AMIX, CONVREC, NRHO, NION, NIMP, NZIMP, NTIME, NSOL, PSI_BND_TYPE, NI_BND_TYPE, TI_BND_TYPE, TE_BND_TYPE, VTOR_BND_TYPE, shot_no, run_no, codeparam, database_format)
process the xml version of the input file from codeparam
subroutine write_equilibrium(path, equilibrium_out)
subroutine assign_code_parameters(codeparameters, return_status)
subroutine write_out(ITIME, COREPROF_NEW, COREPROF_ANALYTIC)
This subroutine stores the results of computations into files.
Module provides routines for testing.
subroutine read_codeparam(in_xml, filename, codeparam)