ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
itm_test_routines.f90
Go to the documentation of this file.
1 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
7 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
9 
10 CONTAINS
11 
12 
13 
14 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
20 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
21  subroutine process_xml &
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)
26 
27  use itm_types
28  use euitm_schemas
29  use euitm_xml_parser
30 
31  implicit none
32 
33  INTEGER :: shot_no !shot number
34  INTEGER :: run_no !run number
35 
36  INTEGER :: nrho !number of radial points (input)
37  INTEGER :: nion !number of ion species (input)
38  INTEGER :: nimp !number of impurity species (input)
39  INTEGER, ALLOCATABLE :: nzimp(:) !number of charge states for each impurity (input)
40  INTEGER :: ntime !number of time points (input)
41 
42  INTEGER :: irho !current radial knot
43  INTEGER :: iion !current ion type
44  INTEGER :: itime !current time step
45 
46  INTEGER :: nsol !Number of analytical example
47  INTEGER :: solver_type !representation of transport equations
48  INTEGER :: sigma_source !origin of Plasma electrical conductivity
49 
50  REAL (R8) :: convrec !required convergency
51  REAL (R8) :: time !Time
52  REAL (R8) :: tau !time step, and mixing coefficient
53  REAL (R8) :: amix !mixing factor
54 
55  INTEGER :: psi_bnd_type !Type of boundary conditions current
56  INTEGER :: ni_bnd_type !Type of boundary conditions ion density
57  INTEGER :: ti_bnd_type !Type of boundary conditions ion temperature
58  INTEGER :: te_bnd_type !Type of boundary conditions electron temperature
59  INTEGER :: vtor_bnd_type !Type of boundary conditions toroidal rotation
60 
61  character (len=32) :: database_format
62 
63  REAL (R8) :: tmp_data(100)
64  integer return_status, n_data
65  type (type_param) :: codeparam
66 
67 ! intial values for parameters
68  database_format = 'mdsplus'
69 
70  call assign_code_parameters(codeparam, return_status)
71 
72  if (return_status /= 0) then
73  write(*, *) 'ERROR: Could not assign code parameters.'
74  stop
75  end if
76 
77 ! deallocate(codeparam%codename, codeparam%codeversion, codeparam%parameters)
78  return
79 
80  contains
81 
82  subroutine assign_code_parameters(codeparameters, return_status)
83 
84  !-----------------------------------------------------------------------
85  ! calls the XML parser for the code parameters and assign the
86  ! resulting values to the corresponding variables
87  !TODO: check an alternative and more elegant solution in Perl
88  !-----------------------------------------------------------------------
89 
90  use mod_f90_kind
91 
92  implicit none
93 
94  type (type_param), intent(in) :: codeparameters
95  integer(ikind), intent(out) :: return_status
96 
97  type(tree) :: parameter_list
98  type(element), pointer :: temp_pointer
99  integer(ikind) :: i, nparm, n_values
100  character(len = 132) :: cname
101 
102  return_status = 0 ! no error
103 
104 !-- parse xml-string codeparameters%parameters
105 
106  call euitm_xml_parse(codeparameters, nparm, parameter_list)
107 
108 !-- assign variables
109 
110  temp_pointer => parameter_list%first
111 
112  outer: do
113  cname = char2str(temp_pointer%cname) ! necessary for AIX
114  select case (cname)
115  case ("parameters")
116  temp_pointer => temp_pointer%child
117  cycle
118 !-- output parameters
119  case ("output")
120  temp_pointer => temp_pointer%child
121  cycle
122  case ("shot")
123  if (allocated(temp_pointer%cvalue)) &
124  call char2num(temp_pointer%cvalue, shot_no)
125  case ("run")
126  if (allocated(temp_pointer%cvalue)) &
127  call char2num(temp_pointer%cvalue, run_no)
128  case ("db")
129  if (allocated(temp_pointer%cvalue)) &
130  database_format = char2str(temp_pointer%cvalue)
131 !-- dims parameters
132  case ("dims")
133  temp_pointer => temp_pointer%child
134  cycle
135  case ("nrho")
136  if (allocated(temp_pointer%cvalue)) &
137  call char2num(temp_pointer%cvalue, nrho)
138  case ("nion")
139  if (allocated(temp_pointer%cvalue)) &
140  call char2num(temp_pointer%cvalue, nion)
141  case ("nimp")
142  if (allocated(temp_pointer%cvalue)) &
143  call char2num(temp_pointer%cvalue, nimp)
144  case ("nzimp")
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)
149  endif
150 !-- solver parameters
151  case ("solver")
152  temp_pointer => temp_pointer%child
153  cycle
154  case ("solver_type")
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)
160  case ("tau")
161  if (allocated(temp_pointer%cvalue)) &
162  call char2num(temp_pointer%cvalue, tau)
163  case ("amix")
164  if (allocated(temp_pointer%cvalue)) &
165  call char2num(temp_pointer%cvalue, amix)
166  case ("convrec")
167  if (allocated(temp_pointer%cvalue)) &
168  call char2num(temp_pointer%cvalue, convrec)
169  case ("ntime")
170  if (allocated(temp_pointer%cvalue)) &
171  call char2num(temp_pointer%cvalue, ntime)
172  case ("nsol")
173  if (allocated(temp_pointer%cvalue)) &
174  call char2num(temp_pointer%cvalue, nsol)
175 !-- boundary parameters
176  case ("boundary")
177  temp_pointer => temp_pointer%child
178  cycle
179  case ("psi_bnd_type")
180  if (allocated(temp_pointer%cvalue)) &
181  call char2num(temp_pointer%cvalue, psi_bnd_type)
182  case ("ni_bnd_type")
183  if (allocated(temp_pointer%cvalue)) &
184  call char2num(temp_pointer%cvalue, ni_bnd_type)
185  case ("ti_bnd_type")
186  if (allocated(temp_pointer%cvalue)) &
187  call char2num(temp_pointer%cvalue, ti_bnd_type)
188  case ("te_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)
194  case default
195  write(*, *) 'ERROR: invalid parameter', cname
196  return_status = 1
197  exit
198  end select
199  do
200  if (associated(temp_pointer%sibling)) then
201  temp_pointer => temp_pointer%sibling
202  exit
203  end if
204  if (associated(temp_pointer%parent, parameter_list%first )) &
205  exit outer
206  if (associated(temp_pointer%parent)) then
207  temp_pointer => temp_pointer%parent
208  else
209  write(*, *) 'ERROR: broken list.'
210  return
211  end if
212  end do
213  end do outer
214 
215 !-- destroy tree
216  call destroy_xml_tree(parameter_list)
217 
218  return
219 
220  end subroutine assign_code_parameters
221 
222 end subroutine process_xml
223 
224 subroutine read_codeparam(in_xml, filename, codeparam)
225 
226  use euitm_schemas
227  use ets_version
228  implicit none
229 
230  integer n_lines, in_xml, ios, i
231  character (len=*) :: filename
232  type (type_codeparam) :: codeparam
233  character(len = 132) :: xml_line
234 
235  open (unit = in_xml, file = filename, status = 'old', &
236  action = 'read', iostat = ios)
237 
238  if (ios /= 0) then
239  write(*,*) 'Could not open ',trim(filename)
240  stop ' ERROR: XML file does not exist '
241  end if
242 
243  n_lines = 0
244 
245  do
246  read (in_xml, '(a)', iostat = ios) xml_line
247  if (ios == 0) then
248  n_lines = n_lines + 1
249  else
250  exit
251  end if
252  end do
253 
254  rewind in_xml
255 
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))
262  do i = 1, n_lines
263  read (in_xml, '(a)', iostat = ios) codeparam%parameters(i)
264  end do
265 
266  close(in_xml)
267 
268  return
269 end subroutine read_codeparam
270 
271 
272 
273 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
279 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
280  SUBROUTINE set_cpo &
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)
284 
285  use itm_types
286  USE euitm_schemas
287  USE ets_plasma
288 
289  IMPLICIT NONE
290 
291  INTEGER :: ifail
292 
293  INTEGER :: nrho !number of radial points (input)
294  INTEGER :: nion !number of ion species (input)
295  INTEGER :: nimp !number of impurity species (input)
296  INTEGER, ALLOCATABLE :: nzimp(:) !number of charge states for each impurity (input)
297  INTEGER :: ntime !number of time points (input)
298 
299  INTEGER :: irho !current radial knot
300  INTEGER :: iion !current ion type
301  INTEGER :: itime !current time step
302 
303  INTEGER :: nsol !Number of analytical example
304 
305  INTEGER :: psi_bnd_type !Type of boundary conditions current
306  INTEGER :: ni_bnd_type !Type of boundary conditions ion density
307  INTEGER :: ti_bnd_type !Type of boundary conditions ion temperature
308  INTEGER :: te_bnd_type !Type of boundary conditions electron temperature
309  INTEGER :: vtor_bnd_type !Type of boundary conditions toroidal rotation
310 
311 ! +++ CPO derived types:
312  TYPE (type_equilibrium), POINTER :: equilibrium(:) !input CPO with geometry quantities
313  TYPE (type_coreprof), POINTER :: coreprof(:) !input/output CPO with plasma profiles
314  TYPE (type_coretransp), POINTER :: coretransp(:) !input CPO with transport coefficients
315 
316 
317 ! +++ Plasma composition:
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))
321 
322  coreprof(1)%composition%zion(:) = 1._r8
323  coreprof(1)%composition%amn(:) = 2._r8
324 
325 
326 ! +++ Generation of grid
327  rho_loop1: DO irho=1,nrho
328  coreprof(1)%rho_tor(irho) = 1.e0_r8/(nrho-1)*(irho-1) !rho in [m]
329 !!!DPC-EQ-4.08b-problem
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 ! added DPC 2012-04-27 to fix a divide by 0 in the analytic solver test
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
337  END DO rho_loop1
338 
339 
340 
341 ! +++ Definition of boundary conditions type
342 
343  coreprof(1)%psi%boundary%type = psi_bnd_type
344  coreprof(1)%te%boundary%type = te_bnd_type
345 
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
350 
351 ! +++ Plasma composition:
352  coreprof(1)%composition%zion(iion) = 1.e0_r8
353  coreprof(1)%composition%amn(iion) = 1.e0_r8
354 
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
358  END IF
359 
360  END DO ion_loop1
361 
362 
363 
364  IF (coreprof(1)%psi%boundary%type.EQ.0) THEN
365  coretransp(1)%values(1)%sigma(:) = 1.e0_r8
366  END IF
367 
368  RETURN
369 
370  END SUBROUTINE set_cpo
371 
372 
373 
374 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
380 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
381  SUBROUTINE set_control &
382  (solver_type,sigma_source,tau,amix,convrec,control)
383 
384  use itm_types
385  USE euitm_schemas
386  USE ets_plasma
387 
388  IMPLICIT NONE
389 
390  INTEGER :: solver_type !representation of transport equations
391 !1-"standard"; 2-"integral"(default)
392  INTEGER :: sigma_source !source for plasma conductivity
393 
394  REAL (R8) :: convrec !required convergency
395  REAL (R8) :: time !Time
396  REAL (R8) :: tau !time step, and mixing coefficient
397  REAL (R8) :: amix !mixing factor
398 
399  TYPE (run_control) :: control !contains all parameters required by run
400 
401  control%SOLVER_TYPE = solver_type !defines the number of numerical solver
402  control%SIGMA_SOURCE = sigma_source !source for plasma conductivity
403  control%TAU = tau !defines the time step
404  control%AMIX = amix !defines the time step
405  control%AMIXTR = amix**0.5 !defines the time step
406  control%CONV = 1.e0_r8 !defines the time step
407  control%CONVREC = convrec !defines the time step
408 
409  RETURN
410 
411  END SUBROUTINE set_control
412 
413 
414 
415 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
416 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
417 
418 
419 
420 
421 
422 
423 
424 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
430 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
431  SUBROUTINE write_out &
432  (itime,coreprof_new, coreprof_analytic)
433 ! This subroutine stores the results of computations
434 ! into files
435 
436  USE euitm_schemas
437 
438  USE type_analytics
439 
440  IMPLICIT NONE
441 
442 ! +++ Input parameters:
443  TYPE (analytical_solution) :: asolution !contains all quantities from analytical solution
444  TYPE (type_coreprof), POINTER :: coreprof_new(:) !input CPO with internal ETS parameters profiles
445  TYPE (type_coreprof), POINTER :: coreprof_analytic(:)!input CPO with internal analytical parameters profiles
446 
447 ! +++ Internal parameters:
448  INTEGER :: irho,iion,itime
449  INTEGER :: nrho,nion
450 
451  CHARACTER (26) filename
452 
453  nrho = SIZE(coreprof_new(1)%rho_tor)
454  nion = SIZE(coreprof_new(1)%composition%amn)
455 
456  write(filename,'(a,i7.7,a)') 'data/OUTPUT/OUT',itime,'.DAT'
457 
458  OPEN (unit=10, file=filename)
459 
460 
461 
462  DO irho = 1, nrho
463 ! 1
464  WRITE (10,'(13(1x,e14.7))') coreprof_new(1)%rho_tor(irho), &
465 ! 2 3
466  coreprof_new(1)%ni%value(irho,nion), coreprof_analytic(1)%ni%value(irho,nion), &
467 ! 4 5
468  coreprof_new(1)%ne%value(irho), coreprof_analytic(1)%ne%value(irho), &
469 ! 6 7
470  coreprof_new(1)%ti%value(irho,nion), coreprof_analytic(1)%ti%value(irho,nion), &
471 ! 8 9
472  coreprof_new(1)%te%value(irho), coreprof_analytic(1)%te%value(irho), &
473 ! 10 11
474  coreprof_new(1)%vtor%value(irho,nion), coreprof_analytic(1)%vtor%value(irho,nion), &
475 ! 12 13
476  coreprof_new(1)%psi%value(irho), coreprof_analytic(1)%psi%value(irho)
477  END DO
478 
479  CLOSE (10)
480 
481 
482  RETURN
483  END SUBROUTINE write_out
484 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
485 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
486 
487 
488 
489 END MODULE itm_test_routines
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)
Definition: emeq.f90:671
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)
Definition: ets_plasma.f90:8
subroutine read_codeparam(in_xml, filename, codeparam)
Definition: emeq.f90:760