22 (solver_type,sigma_source,tau,amix,convrec, &
23 nrho,nion,nimp,nzimp,ntime,nsol, &
24 psi_bnd_type,ni_bnd_type,ti_bnd_type,te_bnd_type,vtor_bnd_type, &
25 shot_no, run_no, codeparam, database_format)
39 INTEGER,
ALLOCATABLE :: nzimp(:)
47 INTEGER :: solver_type
48 INTEGER :: sigma_source
55 INTEGER :: psi_bnd_type
56 INTEGER :: ni_bnd_type
57 INTEGER :: ti_bnd_type
58 INTEGER :: te_bnd_type
59 INTEGER :: vtor_bnd_type
61 character (len=32) :: database_format
63 REAL (R8) :: tmp_data(100)
64 integer return_status, n_data
65 type (type_param
) :: codeparam
68 database_format =
'mdsplus'
72 if (return_status /= 0)
then
73 write(*, *)
'ERROR: Could not assign code parameters.'
94 type (type_param
),
intent(in) :: codeparameters
95 integer(ikind),
intent(out) :: return_status
97 type(tree
) :: parameter_list
98 type(element
),
pointer :: temp_pointer
99 integer(ikind) :: i, nparm, n_values
100 character(len = 132) :: cname
106 call euitm_xml_parse(codeparameters, nparm, parameter_list)
110 temp_pointer => parameter_list%first
113 cname = char2str(temp_pointer%cname)
116 temp_pointer => temp_pointer%child
120 temp_pointer => temp_pointer%child
123 if (
allocated(temp_pointer%cvalue)) &
124 call char2num(temp_pointer%cvalue, shot_no)
126 if (
allocated(temp_pointer%cvalue)) &
127 call char2num(temp_pointer%cvalue, run_no)
129 if (
allocated(temp_pointer%cvalue)) &
130 database_format = char2str(temp_pointer%cvalue)
133 temp_pointer => temp_pointer%child
136 if (
allocated(temp_pointer%cvalue)) &
137 call char2num(temp_pointer%cvalue, nrho)
139 if (
allocated(temp_pointer%cvalue)) &
140 call char2num(temp_pointer%cvalue, nion)
142 if (
allocated(temp_pointer%cvalue)) &
143 call char2num(temp_pointer%cvalue, nimp)
145 if (
allocated(temp_pointer%cvalue))
then
146 call scan_str2real(char2str(temp_pointer%cvalue), tmp_data, n_data)
147 allocate(nzimp(n_data))
148 nzimp=tmp_data(1:n_data)
152 temp_pointer => temp_pointer%child
155 if (
allocated(temp_pointer%cvalue)) &
156 call char2num(temp_pointer%cvalue, solver_type)
157 case (
"sigma_source")
158 if (
allocated(temp_pointer%cvalue)) &
159 call char2num(temp_pointer%cvalue, sigma_source)
161 if (
allocated(temp_pointer%cvalue)) &
162 call char2num(temp_pointer%cvalue, tau)
164 if (
allocated(temp_pointer%cvalue)) &
165 call char2num(temp_pointer%cvalue, amix)
167 if (
allocated(temp_pointer%cvalue)) &
168 call char2num(temp_pointer%cvalue, convrec)
170 if (
allocated(temp_pointer%cvalue)) &
171 call char2num(temp_pointer%cvalue, ntime)
173 if (
allocated(temp_pointer%cvalue)) &
174 call char2num(temp_pointer%cvalue, nsol)
177 temp_pointer => temp_pointer%child
179 case (
"psi_bnd_type")
180 if (
allocated(temp_pointer%cvalue)) &
181 call char2num(temp_pointer%cvalue, psi_bnd_type)
183 if (
allocated(temp_pointer%cvalue)) &
184 call char2num(temp_pointer%cvalue, ni_bnd_type)
186 if (
allocated(temp_pointer%cvalue)) &
187 call char2num(temp_pointer%cvalue, ti_bnd_type)
189 if (
allocated(temp_pointer%cvalue)) &
190 call char2num(temp_pointer%cvalue, te_bnd_type)
191 case (
"vtor_bnd_type")
192 if (
allocated(temp_pointer%cvalue)) &
193 call char2num(temp_pointer%cvalue, vtor_bnd_type)
195 write(*, *)
'ERROR: invalid parameter', cname
200 if (
associated(temp_pointer%sibling))
then
201 temp_pointer => temp_pointer%sibling
204 if (
associated(temp_pointer%parent, parameter_list%first )) &
206 if (
associated(temp_pointer%parent))
then
207 temp_pointer => temp_pointer%parent
209 write(*, *)
'ERROR: broken list.'
216 call destroy_xml_tree(parameter_list)
230 integer n_lines, in_xml, ios, i
231 character (len=*) :: filename
232 type (type_codeparam
) :: codeparam
233 character(len = 132) :: xml_line
235 open (unit = in_xml, file = filename, status =
'old', &
236 action =
'read', iostat = ios)
239 write(*,*)
'Could not open ',trim(filename)
240 stop
' ERROR: XML file does not exist '
246 read (in_xml,
'(a)', iostat = ios) xml_line
248 n_lines = n_lines + 1
256 allocate(codeparam%codename(1))
257 codeparam%codename(1)=
'ETS'
258 allocate(codeparam%codeversion(1))
259 codeparam%codeversion(1)=version
260 write(*,*)
'Code = ',trim(codeparam%codename(1)),
' version = ',trim(codeparam%codeversion(1))
261 allocate(codeparam%parameters(n_lines))
263 read (in_xml,
'(a)', iostat = ios) codeparam%parameters(i)
281 (nrho,nion,nimp,nzimp,ntime,nsol, &
282 psi_bnd_type,ni_bnd_type,ti_bnd_type,te_bnd_type,vtor_bnd_type, &
283 equilibrium,coreprof,coretransp)
296 INTEGER,
ALLOCATABLE :: nzimp(:)
305 INTEGER :: psi_bnd_type
306 INTEGER :: ni_bnd_type
307 INTEGER :: ti_bnd_type
308 INTEGER :: te_bnd_type
309 INTEGER :: vtor_bnd_type
312 TYPE (type_equilibrium
),
POINTER :: equilibrium(:)
313 TYPE (type_coreprof
),
POINTER :: coreprof(:)
314 TYPE (type_coretransp
),
POINTER :: coretransp(:)
318 IF (.not.
associated(coreprof(1)%composition%zion))
ALLOCATE(coreprof(1)%composition%zion(nion))
319 IF (.not.
associated(coreprof(1)%composition%amn))
ALLOCATE(coreprof(1)%composition%amn(nion))
320 IF (.not.
associated(coreprof(1)%composition%zn))
ALLOCATE(coreprof(1)%composition%zn(nion))
322 coreprof(1)%composition%zion(:) = 1._r8
323 coreprof(1)%composition%amn(:) = 2._r8
327 rho_loop1:
DO irho=1,nrho
328 coreprof(1)%rho_tor(irho) = 1.e0_r8/(nrho-1)*(irho-1)
330 equilibrium(1)%profiles_1d%vprime(irho) = coreprof(1)%rho_tor(irho)
331 equilibrium(1)%profiles_1d%volume(irho) = coreprof(1)%rho_tor(irho)**2/2.0_r8
332 equilibrium(1)%profiles_1d%gm3(irho) = 1.e0_r8
333 equilibrium(1)%profiles_1d%gm8(irho) = 1.e0_r8
334 coreprof(1)%toroid_field%r0 = 1.e0_r8
335 coreprof(1)%toroid_field%b0 = 1.e0_r8
336 equilibrium(1)%profiles_1d%F_dia(irho) = coreprof(1)%toroid_field%r0*coreprof(1)%toroid_field%b0
343 coreprof(1)%psi%boundary%type = psi_bnd_type
344 coreprof(1)%te%boundary%type = te_bnd_type
346 ion_loop1:
DO iion=1,nion
347 coreprof(1)%ni%boundary%type(iion) = ni_bnd_type
348 coreprof(1)%ti%boundary%type(iion) = ti_bnd_type
349 coreprof(1)%vtor%boundary%type(iion) = vtor_bnd_type
352 coreprof(1)%composition%zion(iion) = 1.e0_r8
353 coreprof(1)%composition%amn(iion) = 1.e0_r8
355 IF (coreprof(1)%ni%boundary%type(iion).EQ.0)
THEN
356 coreprof(1)%ni%value(:,:) = 1.e0_r8
357 coreprof(1)%ne%value(:) = 1.e0_r8
364 IF (coreprof(1)%psi%boundary%type.EQ.0)
THEN
365 coretransp(1)%values(1)%sigma(:) = 1.e0_r8
382 (solver_type,sigma_source,tau,amix,convrec,control)
390 INTEGER :: solver_type
392 INTEGER :: sigma_source
401 control%SOLVER_TYPE = solver_type
402 control%SIGMA_SOURCE = sigma_source
405 control%AMIXTR = amix**0.5
406 control%CONV = 1.e0_r8
407 control%CONVREC = convrec
432 (itime,coreprof_new, coreprof_analytic)
444 TYPE (type_coreprof
),
POINTER :: coreprof_new(:)
445 TYPE (type_coreprof
),
POINTER :: coreprof_analytic(:)
448 INTEGER :: irho,iion,itime
451 CHARACTER (26) filename
453 nrho =
SIZE(coreprof_new(1)%rho_tor)
454 nion =
SIZE(coreprof_new(1)%composition%amn)
456 write(filename,
'(a,i7.7,a)')
'data/OUTPUT/OUT',itime,
'.DAT'
458 OPEN (unit=10, file=filename)
464 WRITE (10,
'(13(1x,e14.7))') coreprof_new(1)%rho_tor(irho), &
466 coreprof_new(1)%ni%value(irho,nion), coreprof_analytic(1)%ni%value(irho,nion), &
468 coreprof_new(1)%ne%value(irho), coreprof_analytic(1)%ne%value(irho), &
470 coreprof_new(1)%ti%value(irho,nion), coreprof_analytic(1)%ti%value(irho,nion), &
472 coreprof_new(1)%te%value(irho), coreprof_analytic(1)%te%value(irho), &
474 coreprof_new(1)%vtor%value(irho,nion), coreprof_analytic(1)%vtor%value(irho,nion), &
476 coreprof_new(1)%psi%value(irho), coreprof_analytic(1)%psi%value(irho)
The module declares types of variables used in analytical solution.
Module provides routines for testing.
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 assign_code_parameters(codeparameters, return_status)
subroutine write_out(ITIME, COREPROF_NEW, COREPROF_ANALYTIC)
This subroutine stores the results of computations into files.
subroutine set_cpo(NRHO, NION, NIMP, NZIMP, NTIME, NSOL, PSI_BND_TYPE, NI_BND_TYPE, TI_BND_TYPE, TE_BND_TYPE, VTOR_BND_TYPE, EQUILIBRIUM, COREPROF, CORETRANSP)
subroutine set_control(SOLVER_TYPE, SIGMA_SOURCE, TAU, AMIX, CONVREC, CONTROL)
setup control structure
The module declares types of variables used in ETS (transport code)
subroutine read_codeparam(in_xml, filename, codeparam)