ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
itm_test_routines_etseq.f90
Go to the documentation of this file.
1 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
7 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
9 
10 CONTAINS
11 
12 
13 
14 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
20 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
21  SUBROUTINE process_xml( &
22  npsi, nrho, neq_dim1, neq_dim2, max_npoints, &
23 !
24  nnucl, nion, nimp, nzimp, nneut, ncomp, ntype, &
25 !
26  ntime, nsol, &
27 !
28  amn, zn, zion, amn_imp, zn_imp, max_z_imp, &
29 !
30  cold_neutrals, thermal_neutrals, &
31  fast_neutrals, nbi_neutrals, &
32 
33 !
34  psi_type, ne_type, ni_type, te_type, ti_type, &
35  vtor_type,imp_type,n0_type, t0_type, &
36 !
37  psi_value, ne_value, ni_value, te_value, ti_value, &
38  vtor_value, imp_value, n0_value, t0_value, &
39 !
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, &
43  start_time, &
44 !
45  ip, geo_ax, plasma_ax, amin, elong, tria_up, tria_low, &
46 !
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, &
51  tau_min, tau_max, &
52  exp_option, exp_ncols, &
53  evolution_labels, evolution_data, &
54  augment_equil, rho_f, icoronal, &
55  code_parameters)
56 
57 
58  USE itm_types
59  USE euitm_schemas
60  USE euitm_xml_parser
61 
62  IMPLICIT NONE
63 
64  INTEGER :: npsi !number of equilibrium (input)
65  INTEGER :: neq_dim1
66  INTEGER :: neq_dim2
67  INTEGER :: neq_max_npoints
68  INTEGER :: max_npoints
69 
70  INTEGER :: nrho !number of radial points (input)
71  INTEGER :: nnucl
72  INTEGER :: nion !number of ion species (input)
73  INTEGER :: nimp !number of impurity species (input)
74  INTEGER, ALLOCATABLE :: nzimp(:) !number of charge states for each impurity (input)
75  INTEGER :: nneut !number of neutrals (input)
76  INTEGER, ALLOCATABLE :: ncomp(:) !number of components for each neutral
77  INTEGER, ALLOCATABLE :: ntype(:) !number of types for each neutral
78  INTEGER :: ntime !number of time points (input)
79 
80  INTEGER :: irho !current radial knot
81  INTEGER :: iion !current ion type
82  INTEGER :: itime !current time step
83  INTEGER :: iimp
84  INTEGER :: izimp
85 
86  INTEGER :: nsol !Number of analytical example
87  INTEGER :: solver_type !representation of transport equations
88  INTEGER :: sigma_source !origin of Plasma electrical conductivity
89  INTEGER :: quasi_neut !Quasi neutrality:0-electrons; 1-ions from BC; 2-ions fron charge
90  INTEGER :: icoronal !Coronal flag: "0"-OFF; "1" - replace boundary conditions by coronal; "2" - replace boundary conditions and profiles by coronal
91 
92  REAL (R8) :: convrec !required convergency
93  REAL (R8) :: start_time !Start Time
94  REAL (R8) :: tau !time step, and mixing coefficient
95  REAL (R8) :: amix !mixing factor
96 
97  REAL (R8) :: tau_inc !time step increment factor if ITERATIONS < ITER_INC
98  REAL (R8) :: tau_dec !time step decrement factor if ITERATIONS > ITER_DEC
99  INTEGER :: iter_inc !ITERATION limit to cause increase in time-step
100  INTEGER :: iter_dec !ITERATION limit to cause decrease in time-step
101  REAL (R8) :: tau_min !minimum time step
102  REAL (R8) :: tau_max !maximim time step
103  REAL (R8) :: rhon
104 
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(:)
111 
112  INTEGER :: cold_neutrals
113  INTEGER :: thermal_neutrals
114  INTEGER :: fast_neutrals
115  INTEGER :: nbi_neutrals
116 
117  INTEGER :: psi_bnd_type !Type of boundary conditions current
118  INTEGER :: ne_bnd_type !Type of boundary conditions electron density
119  INTEGER :: ni_bnd_type !Type of boundary conditions ion density
120  INTEGER :: ti_bnd_type !Type of boundary conditions ion temperature
121  INTEGER :: te_bnd_type !Type of boundary conditions electron temperature
122  INTEGER :: vtor_bnd_type !Type of boundary conditions toroidal rotation
123  INTEGER :: nimp_bnd_type !Type of boundary conditions toroidal rotation
124  INTEGER :: n0_bnd_type !Type of boundary conditions toroidal rotation
125  INTEGER :: t0_bnd_type !Type of boundary conditions toroidal rotation
126 
127  REAL (R8) :: psi_bnd_value !Value of boundary conditions current
128  REAL (R8) :: ne_bnd_value !Value of boundary conditions electron density
129  REAL (R8), ALLOCATABLE :: ni_bnd_value(:) !Value of boundary conditions ion density
130  REAL (R8), ALLOCATABLE :: ti_bnd_value(:) !Value of boundary conditions ion temperature
131  REAL (R8) :: te_bnd_value !Value of boundary conditions electron temperature
132  REAL (R8), ALLOCATABLE :: vtor_bnd_value(:) !Value of boundary conditions toroidal rotation
133  REAL (R8), ALLOCATABLE :: nimp_bnd_value(:,:) !Value of boundary conditions impurity density
134  REAL (R8), ALLOCATABLE :: n0_bnd_value_cold(:) !Value of boundary conditions neutral ion density
135  REAL (R8), ALLOCATABLE :: n0_bnd_value_thermal(:) !Value of boundary conditions neutral impurity density
136  REAL (R8), ALLOCATABLE :: t0_bnd_value_cold(:) !Value of boundary conditions neutral ion density
137  REAL (R8), ALLOCATABLE :: t0_bnd_value_thermal(:) !Value of boundary conditions neutral impurity density
138 
139 
140  INTEGER :: psi_type
141  REAL (R8) :: psi_value(3)
142  INTEGER :: ne_type
143  REAL (R8) :: ne_value(3)
144  INTEGER :: te_type
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(:,:)
152 
153  INTEGER, ALLOCATABLE :: imp_type(:,:)
154  REAL (R8), ALLOCATABLE :: imp_value(:,:,:)
155 
156  INTEGER, ALLOCATABLE :: n0_type(:,:)
157  REAL (R8), ALLOCATABLE :: n0_value(:,:,:)
158  INTEGER, ALLOCATABLE :: t0_type(:,:)
159  REAL (R8), ALLOCATABLE :: t0_value(:,:,:)
160 
161 
162  REAL (R8) :: ip
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
167  REAL (R8) :: amin
168  REAL (R8) :: elong
169  REAL (R8) :: tria_up
170  REAL (R8) :: tria_low
171 
172  INTEGER :: prof_flag !Flag for primary current quantity: 1-PSI, 2-Q, 3-JPAR
173  INTEGER :: j0_flag !Flag for negative current density: 0-allowed, >0-cut off
174  INTEGER :: q0_flag !Flag for positive dq/drho: 0-allowed, >0-cut off
175  INTEGER :: eq_source
176 
177  INTEGER :: shot_in, run_in !shot and run numbers
178  INTEGER :: interpol !interpolation index
179  INTEGER :: time_dep_input !if 1, time dependence in input data
180  INTEGER :: ext_equil !0: none, 1: BDSEQ, 2: EMEQ, 3: HELENA
181  INTEGER :: equil_mod
182  INTEGER :: augment_equil
183  INTEGER :: ext_source !if 2, call combine_source
184  INTEGER :: ext_transport !if 1, call etaigb and neowes; if 2, call combine_transport
185  REAL (R8) :: add_transport !additional diffusive transport
186  INTEGER :: shot_out, run_out !shot and run numbers
187  REAL (R8) :: tau_out !time step for profiles output into the data base
188  INTEGER :: exp_option
189  INTEGER :: exp_ncols
190  character (len=32) :: db_in, db_out
191  INTEGER, PARAMETER :: buflen = 256
192  CHARACTER(len=BUFLEN) :: rho_f
193 
194  CHARACTER (len=32) :: tmp_labels(100)
195  REAL (R8) :: tmp_data(100*1000)
196 
197  CHARACTER (len=32), POINTER :: evolution_labels(:)
198  REAL (R8), POINTER :: evolution_data(:,:)
199 
200  INTEGER :: return_status, n_labels, n_data, n_rows
201  TYPE (type_param) :: code_parameters
202 
203 
204 
205 ! intial values for parameters
206  shot_in = 4
207  shot_out = 5
208  run_in = 1
209  run_out = 2
210  start_time = 0.0_r8
211  interpol = 1
212  time_dep_input = 0
213  tau = 0.1_r8
214  tau_out = -1.0_r8
215  db_in = 'mdsplus'
216  db_out = 'mdsplus'
217  rhon = 0.95_r8
218 
219  nrho = 50
220  npsi = 100
221  neq_dim1 = 100
222  neq_dim2 = 100
223  neq_max_npoints = 100
224 
225  nion = 1
226  nimp = 0
227  nneut = 0
228 
229  cold_neutrals = 0
230  thermal_neutrals = 0
231  fast_neutrals = 0
232  nbi_neutrals = 0
233 
234  solver_type = 3
235  sigma_source = 1
236  amix = 1.0_r8
237  convrec = 1.0e-4_r8
238  ntime = 100
239  nsol = 2
240 
241  psi_bnd_type = 2
242  ne_bnd_type = 0
243  ni_bnd_type = 1
244  ti_bnd_type = 1
245  te_bnd_type = 1
246  vtor_bnd_type = 1
247  nimp_bnd_type = 1
248  n0_bnd_type = 1
249  t0_bnd_type = 1
250 
251  ext_equil = 2
252  equil_mod = 0
253  augment_equil = 0
254  ext_source = 0
255  ext_transport = 0
256  add_transport = 0.0_r8
257  tau_inc = 0.0_r8
258  tau_dec = 0.0_r8
259  iter_inc = 0
260  iter_dec = 0
261  tau_min = 0.0_r8
262  tau_max = 0.0_r8
263  exp_option = 0
264  prof_flag = 0
265  j0_flag = 1
266  rho_f = '1.0'
267  quasi_neut = 0
268  icoronal = 0
269 
270 
271 
272 
273  CALL assign_code_parameters(code_parameters, return_status, &
274  nzimp, ncomp, ntype, max_npoints, &
275 !
276  amn, zn, zion, amn_imp, zn_imp, max_z_imp, &
277 !
278  ni_bnd_value, ti_bnd_value, vtor_bnd_value, nimp_bnd_value, &
279 !
280  n0_bnd_value_cold, n0_bnd_value_thermal, &
281 !
282  t0_bnd_value_cold, t0_bnd_value_thermal)
283 
284  if(allocated(nzimp)) then
285  write(*,*) 'process_xml: nzimp allocated'
286  write(*,*) 'nzimp = ', nzimp
287  else
288  write(*,*) 'process_xml: nzimp not allocated'
289  endif
290 
291 
292  ALLOCATE (ni_type(nion))
293  ALLOCATE (ti_type(nion))
294  ALLOCATE (vtor_type(nion))
295 
296  ALLOCATE (ni_value(3,nion))
297  ALLOCATE (ti_value(3,nion))
298  ALLOCATE (vtor_value(3,nion))
299 
300  if(nimp.gt.0) then
301  ALLOCATE (imp_type(nimp,maxval(nzimp)))
302  ALLOCATE (imp_value(nimp,3,maxval(nzimp)))
303  endif
304 
305  write(*,*) 'NNEUT = ', nneut
306  if(nneut.gt.0) then
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)))
311  endif
312 
313 
314  psi_type = psi_bnd_type
315  psi_value = 0._r8
316  psi_value(1) = psi_bnd_value
317  ne_type = ne_bnd_type
318  ne_value = 0._r8
319  ne_value(1) = ne_bnd_value
320  te_type = te_bnd_type
321  te_value = 0._r8
322  te_value(1) = te_bnd_value
323  ni_type(:) = ni_bnd_type
324  ni_value = 0._r8
325  ni_value(1,:) = ni_bnd_value(:)
326  ti_type(:) = ti_bnd_type
327  ti_value = 0._r8
328  ti_value(1,:) = te_bnd_value
329  vtor_type(:) = vtor_bnd_type
330  vtor_value = 0._r8
331  vtor_value(1,:) = vtor_bnd_value(:)
332 
333  if(nimp .gt. 0) then
334  imp_type(:,:) = nimp_bnd_type
335  imp_value = 0._r8
336  DO iimp =1,nimp
337  DO izimp = 1, nzimp(iimp)
338  imp_value(iimp,1,izimp)= nimp_bnd_value(iimp,izimp)
339  END DO
340  END DO
341  endif
342 
343  if(nneut.gt.0) then
344  n0_type(:,:) = n0_bnd_type
345  t0_type(:,:) = t0_bnd_type
346  n0_value = 0._r8
347  t0_value = 0._r8
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(:)
352 
353 
354  end if
355 
356 ! update parameters
357  IF(tau_out .LT. 0.0_r8) tau_out = 0.1_r8
358 
359  IF (return_status /= 0) THEN
360  WRITE(*, *) 'ERROR: Could not assign code parameters.'
361  stop
362  END IF
363 
364  RETURN
365 
366  CONTAINS
367 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++
368 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++
369 
370 
371 
372 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++
373 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++
374  SUBROUTINE assign_code_parameters(codeparameters, return_status,&
375  nzimp, ncomp, ntype, max_npoints, &
376 !
377  amn, zn, zion, amn_imp, zn_imp, max_z_imp, &
378 !
379  ni_bnd_value, ti_bnd_value, vtor_bnd_value, nimp_bnd_value, &
380 !
381  n0_bnd_value_cold, n0_bnd_value_thermal, &
382 !
383  t0_bnd_value_cold, t0_bnd_value_thermal)
384 
385  !-----------------------------------------------------------------------
386  ! calls the XML parser for the code parameters and assign the
387  ! resulting values to the corresponding variables
388  !TODO: check an alternative and more elegant solution in Perl
389  !-----------------------------------------------------------------------
390 
391  USE mod_f90_kind
392 
393  IMPLICIT NONE
394 
395  TYPE (type_param), INTENT(in) :: codeparameters
396  INTEGER(ikind), INTENT(out) :: return_status
397 
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
406 
407  INTEGER, ALLOCATABLE :: nzimp(:) !number of charge states for each impurity (input)
408  INTEGER, ALLOCATABLE :: ncomp(:) !number of components for each neutral
409  INTEGER, ALLOCATABLE :: ntype(:) !number of types for each neutral
410  INTEGER :: max_npoints !number of equilibrium boundary points
411 
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(:)
418 
419  REAL (R8), ALLOCATABLE :: ni_bnd_value(:) !Value of boundary conditions ion density
420  REAL (R8), ALLOCATABLE :: ti_bnd_value(:) !Value of boundary conditions ion temperature
421  REAL (R8), ALLOCATABLE :: vtor_bnd_value(:) !Value of boundary conditions toroidal rotation
422  REAL (R8), ALLOCATABLE :: nimp_bnd_value(:,:) !Value of boundary conditions impurity density
423  REAL (R8), ALLOCATABLE :: n0_bnd_value_cold(:) !Value of boundary conditions neutral ion density
424  REAL (R8), ALLOCATABLE :: n0_bnd_value_thermal(:) !Value of boundary conditions neutral impurity density
425  REAL (R8), ALLOCATABLE :: t0_bnd_value_cold(:) !Value of boundary conditions neutral ion density
426  REAL (R8), ALLOCATABLE :: t0_bnd_value_thermal(:) !Value of boundary conditions neutral impurity density
427 
428  return_status = 0 ! no error
429 
430 !-- parse xml-string codeparameters%parameters
431 
432  WRITE(*,*) 'Calling euitm_xml_parse'
433  CALL euitm_xml_parse(code_parameters, nparm, parameter_list)
434  WRITE(*,*) 'Called euitm_xml_parse'
435 
436 !-- assign variables
437 
438  temp_pointer => parameter_list%first
439 
440  outer: DO
441  cname = char2str(temp_pointer%cname) ! necessary for AIX
442  SELECT CASE (cname)
443  CASE ("parameters")
444  temp_pointer => temp_pointer%child
445  cycle
446 
447 !-- input parameters
448  CASE ("input")
449  temp_pointer => temp_pointer%child
450  cycle
451  CASE ("shot_in")
452  IF (ALLOCATED(temp_pointer%cvalue)) &
453  CALL char2num(temp_pointer%cvalue, shot_in)
454  CASE ("run_in")
455  IF (ALLOCATED(temp_pointer%cvalue)) &
456  CALL char2num(temp_pointer%cvalue, run_in)
457  CASE ("interpol")
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)
463  case ("db_in")
464  if (allocated(temp_pointer%cvalue)) &
465  db_in = char2str(temp_pointer%cvalue)
466 
467 
468 !-- output parameters
469  CASE ("output")
470  temp_pointer => temp_pointer%child
471  cycle
472  CASE ("shot_out")
473  IF (ALLOCATED(temp_pointer%cvalue)) &
474  CALL char2num(temp_pointer%cvalue, shot_out)
475  CASE ("run_out")
476  IF (ALLOCATED(temp_pointer%cvalue)) &
477  CALL char2num(temp_pointer%cvalue, run_out)
478  CASE ("tau_out")
479  IF (ALLOCATED(temp_pointer%cvalue)) &
480  CALL char2num(temp_pointer%cvalue, tau_out)
481  case ("db_out")
482  if (allocated(temp_pointer%cvalue)) &
483  db_out = char2str(temp_pointer%cvalue)
484 
485 
486 
487 !-- solver parameters
488  CASE ("solver")
489  temp_pointer => temp_pointer%child
490  cycle
491  CASE ("rho")
492  IF (ALLOCATED(temp_pointer%cvalue)) &
493  rho_f = char2str(temp_pointer%cvalue)
494  CASE ("solver_type")
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)
500  CASE ("tau")
501  IF (ALLOCATED(temp_pointer%cvalue)) &
502  CALL char2num(temp_pointer%cvalue, tau)
503  CASE ("tau_inc")
504  IF (ALLOCATED(temp_pointer%cvalue)) &
505  CALL char2num(temp_pointer%cvalue, tau_inc)
506  CASE ("tau_dec")
507  IF (ALLOCATED(temp_pointer%cvalue)) &
508  CALL char2num(temp_pointer%cvalue, tau_dec)
509  CASE ("iter_inc")
510  IF (ALLOCATED(temp_pointer%cvalue)) &
511  CALL char2num(temp_pointer%cvalue, iter_inc)
512  CASE ("iter_dec")
513  IF (ALLOCATED(temp_pointer%cvalue)) &
514  CALL char2num(temp_pointer%cvalue, iter_dec)
515  CASE ("tau_min")
516  IF (ALLOCATED(temp_pointer%cvalue)) &
517  CALL char2num(temp_pointer%cvalue, tau_min)
518  CASE ("tau_max")
519  IF (ALLOCATED(temp_pointer%cvalue)) &
520  CALL char2num(temp_pointer%cvalue, tau_max)
521  CASE ("amix")
522  IF (ALLOCATED(temp_pointer%cvalue)) &
523  CALL char2num(temp_pointer%cvalue, amix)
524  CASE ("convrec")
525  IF (ALLOCATED(temp_pointer%cvalue)) &
526  CALL char2num(temp_pointer%cvalue, convrec)
527  CASE ("ntime")
528  IF (ALLOCATED(temp_pointer%cvalue)) &
529  CALL char2num(temp_pointer%cvalue, ntime)
530  CASE ("start_time")
531  IF (ALLOCATED(temp_pointer%cvalue)) &
532  CALL char2num(temp_pointer%cvalue, start_time)
533  CASE ("nsol")
534  IF (ALLOCATED(temp_pointer%cvalue)) &
535  CALL char2num(temp_pointer%cvalue, nsol)
536  CASE ("ext_equil")
537  IF (ALLOCATED(temp_pointer%cvalue)) &
538  CALL char2num(temp_pointer%cvalue, ext_equil)
539  case ("equil_mod")
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)
545  CASE ("ext_source")
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)
554  CASE ("quasi_neut")
555  IF (ALLOCATED(temp_pointer%cvalue)) &
556  CALL char2num(temp_pointer%cvalue, quasi_neut)
557  CASE ("icoronal")
558  IF (ALLOCATED(temp_pointer%cvalue)) &
559  CALL char2num(temp_pointer%cvalue, icoronal)
560 
561 !-- startup
562  CASE ("startup")
563  temp_pointer => temp_pointer%child
564  cycle
565  CASE ("prof_flag")
566  IF (ALLOCATED(temp_pointer%cvalue)) &
567  CALL char2num(temp_pointer%cvalue, prof_flag)
568  CASE ("j0_flag")
569  IF (ALLOCATED(temp_pointer%cvalue)) &
570  CALL char2num(temp_pointer%cvalue, j0_flag)
571  CASE ("q0_flag")
572  IF (ALLOCATED(temp_pointer%cvalue)) &
573  CALL char2num(temp_pointer%cvalue, q0_flag)
574 
575 
576 !-- dims parameters
577  CASE ("dims")
578  temp_pointer => temp_pointer%child
579  cycle
580  CASE ("npsi")
581  IF (ALLOCATED(temp_pointer%cvalue)) &
582  CALL char2num(temp_pointer%cvalue, npsi)
583  CASE ("neq_dim1")
584  IF (ALLOCATED(temp_pointer%cvalue)) &
585  CALL char2num(temp_pointer%cvalue, neq_dim1)
586  CASE ("neq_dim2")
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)
592  CASE ("nrho")
593  IF (ALLOCATED(temp_pointer%cvalue)) &
594  CALL char2num(temp_pointer%cvalue, nrho)
595 
596 
597 
598 !-- output parameters
599  CASE ("equilibrium")
600  temp_pointer => temp_pointer%child
601  cycle
602  CASE ("ip")
603  IF (ALLOCATED(temp_pointer%cvalue)) &
604  CALL char2num(temp_pointer%cvalue, ip)
605  CASE ("r_geo")
606  IF (ALLOCATED(temp_pointer%cvalue)) &
607  CALL char2num(temp_pointer%cvalue, r_geo)
608  CASE ("z_geo")
609  IF (ALLOCATED(temp_pointer%cvalue)) &
610  CALL char2num(temp_pointer%cvalue, z_geo)
611  CASE ("b_geo")
612  IF (ALLOCATED(temp_pointer%cvalue)) &
613  CALL char2num(temp_pointer%cvalue, b_geo)
614  CASE ("r_plasma")
615  IF (ALLOCATED(temp_pointer%cvalue)) &
616  CALL char2num(temp_pointer%cvalue, r_plasma)
617  CASE ("z_plasma")
618  IF (ALLOCATED(temp_pointer%cvalue)) &
619  CALL char2num(temp_pointer%cvalue, z_plasma)
620  CASE ("b_plasma")
621  IF (ALLOCATED(temp_pointer%cvalue)) &
622  CALL char2num(temp_pointer%cvalue, b_plasma)
623  CASE ("amin")
624  IF (ALLOCATED(temp_pointer%cvalue)) &
625  CALL char2num(temp_pointer%cvalue, amin)
626  CASE ("elong")
627  IF (ALLOCATED(temp_pointer%cvalue)) &
628  CALL char2num(temp_pointer%cvalue, elong)
629  CASE ("tria_up")
630  IF (ALLOCATED(temp_pointer%cvalue)) &
631  CALL char2num(temp_pointer%cvalue, tria_up)
632  CASE ("tria_low")
633  IF (ALLOCATED(temp_pointer%cvalue)) &
634  CALL char2num(temp_pointer%cvalue, tria_low)
635  CASE ("eq_source")
636  IF (ALLOCATED(temp_pointer%cvalue)) &
637  CALL char2num(temp_pointer%cvalue, eq_source)
638 
639  geo_ax(1) = r_geo
640  geo_ax(2) = z_geo
641  geo_ax(3) = b_geo
642 
643  plasma_ax(1) = r_plasma
644  plasma_ax(2) = z_plasma
645  plasma_ax(3) = b_plasma
646 
647 !-- compositions
648  CASE ("compositions")
649  temp_pointer => temp_pointer%child
650  cycle
651  CASE ("ions")
652  temp_pointer => temp_pointer%child
653  cycle
654  CASE ("amn")
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)
659 
660  CASE ("zn")
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)
665 
666  CASE ("zion")
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)
671 
672 
673  nion = min(n_data1, n_data2, n_data3)
674 
675  CASE ("impurity")
676  temp_pointer => temp_pointer%child
677  cycle
678  CASE ("amn_imp")
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)
683  else
684  n_data1 = 0
685  endif
686 
687  CASE ("zn_imp")
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)
692  else
693  n_data2 = 0
694  endif
695 
696  CASE ("max_z_imp")
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)
701  else
702  n_data3 = 0
703  endif
704 
705  nimp = min(n_data1, n_data2, n_data3)
706  if(nimp .gt. 0) then
707  ALLOCATE (nzimp(nimp))
708  nzimp = nint(max_z_imp)
709  endif
710 
711  CASE ("neutrals")
712  temp_pointer => temp_pointer%child
713  cycle
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
730 
731 
732 
733 
734  nnucl = nion + nimp !assummption of all species being different
735 
736  if(cold_neutrals + thermal_neutrals + fast_neutrals + nbi_neutrals.eq.0) then
737  nneut=0
738  else
739  nneut = nion + nimp !assummption of all species being different
740  ALLOCATE (ncomp(nneut))
741  ALLOCATE (ntype(nneut))
742  ncomp = 1 !assumption: single atoms
743  ntype = cold_neutrals + thermal_neutrals + fast_neutrals + nbi_neutrals
744  endif
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))
753 
754 
755 
756 !-- boundary parameters
757  CASE ("boundary")
758  temp_pointer => temp_pointer%child
759  cycle
760  CASE ("type")
761  temp_pointer => temp_pointer%child
762  cycle
763  CASE ("psi_bnd_type")
764  IF (ALLOCATED(temp_pointer%cvalue)) &
765  CALL char2num(temp_pointer%cvalue, psi_bnd_type)
766  CASE ("ne_bnd_type")
767  IF (ALLOCATED(temp_pointer%cvalue)) &
768  CALL char2num(temp_pointer%cvalue, ne_bnd_type)
769  CASE ("ni_bnd_type")
770  IF (ALLOCATED(temp_pointer%cvalue)) &
771  CALL char2num(temp_pointer%cvalue, ni_bnd_type)
772  CASE ("ti_bnd_type")
773  IF (ALLOCATED(temp_pointer%cvalue)) &
774  CALL char2num(temp_pointer%cvalue, ti_bnd_type)
775  CASE ("te_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)
784  CASE ("n0_bnd_type")
785  IF (ALLOCATED(temp_pointer%cvalue)) &
786  CALL char2num(temp_pointer%cvalue, n0_bnd_type)
787  CASE ("t0_bnd_type")
788  IF (ALLOCATED(temp_pointer%cvalue)) &
789  CALL char2num(temp_pointer%cvalue, t0_bnd_type)
790 
791 
792 
793  CASE ("value")
794  temp_pointer => temp_pointer%child
795  cycle
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)
806 
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)
811 
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)
819 
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
824  write(*,*) nimp
825  nn=0
826  DO iimp =1,nimp
827  DO izimp = 1, nzimp(iimp)
828  IF ((nn+izimp).LE.n_data) &
829  nimp_bnd_value(iimp,izimp) = real_data(nn+izimp)
830  END DO
831  nn = nn + nzimp(iimp)
832 ! NN=0
833 ! DO IIMP =1,NIMP
834 ! DO IZIMP = 1, NZIMP(IIMP)
835 ! NN = NN + 1
836 ! IF (NN.LE.n_data) &
837 ! nimp_bnd_value(IIMP,IZIMP) = real_data(NN)
838 ! END DO
839  END DO
840  endif
841 
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)
846 
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)
851 
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)
856 
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)
861 
862 
863 
864 !-- experimental parameters
865  CASE ("experimental")
866  temp_pointer => temp_pointer%child
867  cycle
868  CASE ("option")
869  IF (ALLOCATED(temp_pointer%cvalue)) &
870  CALL char2num(temp_pointer%cvalue, exp_option)
871  CASE ("ncolumns")
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)
879  ENDIF
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'
886  ENDIF
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'
891  ENDIF
892  ALLOCATE(evolution_data(exp_ncols, n_rows))
893  evolution_data=reshape(tmp_data(1:n_data),(/ exp_ncols, n_rows /))
894  ENDIF
895 
896 
897 !-- default
898  CASE default
899  WRITE(*, *) 'ERROR: invalid parameter', cname
900  return_status = 1
901  EXIT
902  END SELECT
903  DO
904  IF (ASSOCIATED(temp_pointer%sibling)) THEN
905  temp_pointer => temp_pointer%sibling
906  EXIT
907  END IF
908  IF (ASSOCIATED(temp_pointer%parent, parameter_list%first )) &
909  EXIT outer
910  IF (ASSOCIATED(temp_pointer%parent)) THEN
911  temp_pointer => temp_pointer%parent
912  ELSE
913  WRITE(*, *) 'ERROR: broken list.'
914  RETURN
915  END IF
916  END DO
917  END DO outer
918 
919  !-- destroy tree
920  CALL destroy_xml_tree(parameter_list)
921 
922  if(allocated(nzimp)) then
923  write(*,*) 'assign_code_parameters: nzimp allocated'
924  write(*,*) 'nzimp = ', nzimp
925  else
926  write(*,*) 'assign_code_parameters: nzimp not allocated'
927  endif
928 
929  RETURN
930 
931  END SUBROUTINE assign_code_parameters
932 
933  END SUBROUTINE process_xml
934 
935  SUBROUTINE read_codeparam(in_xml, filename, codeparam)
936 
937  USE euitm_schemas
938  USE ets_version
939  IMPLICIT NONE
940 
941  INTEGER n_lines, in_xml, ios, i
942  CHARACTER (len=*) :: filename
943  TYPE (type_codeparam) :: codeparam
944  CHARACTER(len = 132) :: xml_line
945 
946  OPEN (unit = in_xml, file = filename, status = 'old', &
947  action = 'read', iostat = ios)
948 
949  IF (ios /= 0) THEN
950  WRITE(*,*) 'Could not open ',trim(filename)
951  stop ' ERROR: XML file does not exist '
952  END IF
953 
954  n_lines = 0
955 
956  DO
957  READ (in_xml, '(a)', iostat = ios) xml_line
958  IF (ios == 0) THEN
959  n_lines = n_lines + 1
960  ELSE
961  EXIT
962  END IF
963  END DO
964 
965  rewind in_xml
966 
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))
973  DO i = 1, n_lines
974  READ (in_xml, '(a)', iostat = ios) codeparam%parameters(i)
975  END DO
976 
977  CLOSE(in_xml)
978 
979  RETURN
980  END SUBROUTINE read_codeparam
981 
982 
983 
984 
985 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
991 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
992 !DPC 2009-01-29 SUBROUTINE WRITE_OUTPUT &
993  SUBROUTINE write_out (ITIME, COREPROF)
994 ! This subroutine stores the results of computations
995 ! into files
996 
997  USE euitm_schemas
998 
999  IMPLICIT NONE
1000 
1001 ! +++ Input parameters:
1002  TYPE (type_coreprof), POINTER :: coreprof(:) !input CPO with internal ETS parameters profiles
1003 
1004 ! +++ Internal parameters:
1005  INTEGER :: irho,iion,itime
1006  INTEGER :: nrho,nion
1007 
1008  CHARACTER (33) filename
1009 
1010  nrho = SIZE(coreprof(1)%rho_tor)
1011  nion = SIZE(coreprof(1)%compositions%ions)
1012 
1013  WRITE(filename,'(a,i7.7,a)') 'eq_ets_data/OUTPUT/OUT',itime,'.DAT'
1014 
1015  OPEN (unit=10, file=filename)
1016 
1017 
1018 
1019  DO irho = 1, nrho
1020 ! 1
1021  WRITE (10,'(10(1x,e16.8))') coreprof(1)%rho_tor(irho), &
1022 ! 2
1023  coreprof(1)%ni%value(irho,nion), &
1024 ! 3
1025  coreprof(1)%ne%value(irho), &
1026 ! 4
1027  coreprof(1)%ti%value(irho,nion), &
1028 ! 5
1029  coreprof(1)%te%value(irho), &
1030 ! 6
1031  coreprof(1)%vtor%value(irho,nion), &
1032 ! 7
1033  coreprof(1)%psi%value(irho), &
1034 ! 8
1035  coreprof(1)%profiles1d%jtot%value(irho), &
1036 ! 9
1037  coreprof(1)%profiles1d%q%value(irho), &
1038 ! 10
1039  coreprof(1)%profiles1d%zeff%value(irho)
1040  END DO
1041 
1042  CLOSE (10)
1043 
1044 
1045  RETURN
1046  END SUBROUTINE write_out
1047 !DPC 2009-01-29 END SUBROUTINE WRITE_OUTPUT
1048 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1049 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1050 
1051 
1052 
1053 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1058 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1059  SUBROUTINE write_equilibrium (ITIME,EQUILIBRIUM)
1060 ! This subroutine stores the results of computations
1061 ! into files
1062 
1063  USE euitm_schemas
1064 
1065  IMPLICIT NONE
1066 
1067 ! +++ Input parameters:
1068  TYPE (type_equilibrium), POINTER :: equilibrium(:)
1069 
1070 ! +++ Internal parameters:
1071  INTEGER :: irho,itime
1072  INTEGER :: nrho
1073 
1074  CHARACTER (35) filename
1075 
1076  nrho = SIZE(equilibrium(1)%profiles_1d%rho_tor)
1077  WRITE(*,*) "ITIME=",itime
1078 
1079  WRITE(filename,'(a,i7.7,a)') 'eq_ets_data/OUTPUT/EQOUT',itime,'.DAT'
1080 
1081  OPEN (unit=10, file=filename)
1082 
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)
1099 
1100  DO irho = 1, nrho
1101 ! 1
1102  WRITE (10,'(16(1x,e16.8))') equilibrium(1)%profiles_1d%rho_tor(irho), &
1103 ! 2 3
1104  equilibrium(1)%profiles_1d%q(irho), equilibrium(1)%profiles_1d%pressure(irho), &
1105 ! 4 5
1106  equilibrium(1)%profiles_1d%jparallel(irho), equilibrium(1)%profiles_1d%gm1(irho), &
1107 ! 6 7
1108  equilibrium(1)%profiles_1d%gm2(irho), equilibrium(1)%profiles_1d%gm3(irho), &
1109 ! 8 9
1110  equilibrium(1)%profiles_1d%gm4(irho), equilibrium(1)%profiles_1d%gm5(irho), &
1111 ! 10 11
1112  equilibrium(1)%profiles_1d%gm6(irho), equilibrium(1)%profiles_1d%gm7(irho), &
1113 ! 12 13
1114  equilibrium(1)%profiles_1d%volume(irho), equilibrium(1)%profiles_1d%vprime(irho), &
1115 ! 14 15
1116  equilibrium(1)%profiles_1d%area(irho), equilibrium(1)%profiles_1d%aprime(irho), &
1117 ! 16
1118  equilibrium(1)%profiles_1d%F_dia(irho)
1119  END DO
1120 
1121  CLOSE (10)
1122 
1123 
1124  RETURN
1125  END SUBROUTINE write_equilibrium
1126 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1127 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1128 
1129 
1130 
1131 END MODULE itm_test_routines_etseq
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)
Definition: emeq.f90:671
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)
Definition: emeq.f90:760