44 use deallocate_structures
58 INTEGER,
PARAMETER :: nslice = 1
63 INTEGER,
ALLOCATABLE,
SAVE :: nzimp(:)
66 INTEGER,
ALLOCATABLE,
SAVE :: ncomp(:)
67 INTEGER,
ALLOCATABLE,
SAVE :: ntype(:)
70 REAL (R8),
ALLOCATABLE,
SAVE :: amn(:)
71 REAL (R8),
ALLOCATABLE,
SAVE :: zn(:)
72 REAL (R8),
ALLOCATABLE,
SAVE :: zion(:)
73 REAL (R8),
ALLOCATABLE,
SAVE :: amn_imp(:)
74 REAL (R8),
ALLOCATABLE,
SAVE :: zn_imp(:)
75 REAL (R8),
ALLOCATABLE,
SAVE :: max_z_imp(:)
77 INTEGER :: cold_neutrals
78 INTEGER :: thermal_neutrals
79 INTEGER :: fast_neutrals
80 INTEGER :: nbi_neutrals
87 INTEGER :: solver_type
89 INTEGER :: sigma_source
96 INTEGER,
PARAMETER :: maxiter=1000
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
107 TYPE (type_equilibrium
),
POINTER :: equilibrium_old(:)
108 TYPE (type_equilibrium
),
POINTER :: equilibrium_iter(:)
109 TYPE (type_coreprof
),
POINTER :: coreprof_old(:)
110 TYPE (type_coreprof
),
POINTER :: coreprof_new(:)
111 TYPE (type_coreprof
),
POINTER :: coreprof_iter(:)
112 TYPE (type_coreprof
),
POINTER :: coreprof_analytic(:)
113 TYPE (type_coretransp
),
POINTER :: coretransp(:)
114 TYPE (type_coresource
),
POINTER :: coresource(:)
115 TYPE (type_coreimpur
),
POINTER :: coreimpur(:)
116 type (type_param
) :: code_parameters, ets_parameters
117 character (len=32) :: database_format
119 INTEGER :: control_integer(4)
120 REAL (R8) :: control_double(6)
130 equilibrium,coreprof,coretransp,coresource,coreimpur, code_parameters)
140 TYPE (type_coreprof
),
POINTER :: coreprof_in(:)
142 TYPE (type_equilibrium
),
POINTER :: equilibrium(:)
143 TYPE (type_coreprof
),
POINTER :: coreprof(:)
144 TYPE (type_coretransp
),
POINTER :: coretransp(:)
145 TYPE (type_coresource
),
POINTER :: coresource(:)
146 TYPE (type_coreimpur
),
POINTER :: coreimpur(:)
147 type (type_param
) :: code_parameters
152 (coreprof_old, coreprof_iter, coreprof_new, &
153 equilibrium_old, equilibrium_iter, &
154 coretransp, coresource, coreimpur, &
155 control_integerx, control_doublex, ets_parameters)
164 TYPE (type_equilibrium
),
POINTER :: equilibrium_old(:), equilibrium_iter(:)
165 TYPE (type_coreprof
),
POINTER :: coreprof_old(:), coreprof_iter(:)
166 TYPE (type_coretransp
),
POINTER :: coretransp(:)
167 TYPE (type_coresource
),
POINTER :: coresource(:)
168 TYPE (type_coreimpur
),
POINTER :: coreimpur(:)
169 INTEGER :: control_integerx(4)
170 REAL (R8) :: control_doublex(5)
172 TYPE (type_coreprof
),
POINTER :: coreprof_new(:)
173 type (type_param
) :: ets_parameters
175 end subroutine itmets
177 subroutine convergence(COREPROF_ITER, COREPROF_OUT, CONTROL_DOUBLE)
186 TYPE (type_coreprof
),
POINTER :: coreprof_iter(:)
187 TYPE (type_coreprof
),
POINTER :: coreprof_out(:)
190 REAL (R8) :: control_double(5)
192 end subroutine convergence
211 call fill_param(ets_parameters,
'XML/ets.xml',
'',
'XML/ets.xsd')
212 call fill_param(code_parameters,
'XML/ets_analytics.xml',
'',
'XML/ets_analytics.xsd')
213 CALL
process_xml(solver_type,sigma_source,tau,amix,convrec,nrho,nion,nimp,nzimp,ntime,nsol, &
214 psi_bnd_type,ni_bnd_type,ti_bnd_type,te_bnd_type,vtor_bnd_type, &
215 shot_no, run_no, code_parameters, database_format)
222 call
set_control(solver_type,sigma_source,tau,amix,convrec,control)
223 control_integer(1) = control%SOLVER_TYPE
224 control_integer(2) = control%SIGMA_SOURCE
225 control_double(1) = control%TAU
226 control_double(2) = control%AMIX
227 control_double(3) = control%AMIXTR
228 control_double(4) = control%CONV
229 control_double(5) = control%CONVREC
240 if(shot_no.gt.0.and.run_no.ge.0)
then
242 write(*,*)
'Using ', trim(database_format),
' for the backend'
243 select case (database_format)
245 call euitm_create(
'euitm',shot_no,run_no,0,0,idx)
247 call euitm_create_hdf5(
'euitm',shot_no,run_no,0,0,idx)
249 write(*,*)
'Unexpected database format choice : ',trim(database_format)
250 stop
'Error: unrecognized database format'
261 ALLOCATE (ncomp(nneut))
262 ALLOCATE (ntype(nneut))
266 CALL
allocate_coreprof_cpo(nslice, nrho, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, coreprof_old)
267 CALL
allocate_coreprof_cpo(nslice, nrho, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, coreprof_iter)
271 ALLOCATE (zion(nion))
272 ALLOCATE (amn_imp(nimp))
273 ALLOCATE (zn_imp(nimp))
274 ALLOCATE (max_z_imp(nimp))
291 amn_imp, zn_imp, max_z_imp, &
293 cold_neutrals, thermal_neutrals,&
294 fast_neutrals, nbi_neutrals)
296 call deallocate_cpo(coreprof_old(1)%COMPOSITIONS)
297 CALL copy_cpo(coreprof_iter(1)%COMPOSITIONS, coreprof_old(1)%COMPOSITIONS)
300 allocate(coreprof_old(1)%codeparam%codename(1))
301 coreprof_old(1)%codeparam%codename(1)=
'solver_test'
302 allocate(coreprof_old(1)%codeparam%codeversion(1))
303 coreprof_old(1)%codeparam%codeversion(1)=version
304 allocate(coreprof_old(1)%codeparam%parameters(
size(code_parameters%parameters)))
305 coreprof_old(1)%codeparam%parameters=code_parameters%parameters
319 coretransp, coresource, coreimpur, code_parameters)
326 call deallocate_cpo(coreprof_old)
327 call copy_cpo(coreprof_analytic,coreprof_old)
328 CALL deallocate_cpo(coreprof_analytic)
329 CALL deallocate_cpo(coretransp )
330 CALL deallocate_cpo(coresource )
331 CALL deallocate_cpo(coreimpur )
340 time_loop1:
DO itime = 1,ntime
344 WRITE (6,*)
'========================================'
345 WRITE (6,*)
'TIME=',time
346 WRITE (6,*)
'========================================'
356 CALL
analytical_plasma(time, coreprof_old, equilibrium_iter, coreprof_analytic, &
357 coretransp, coresource, coreimpur, code_parameters)
370 call copy_cpo(coreprof_old,coreprof_iter)
385 if(iter.gt.maxiter)
then
386 write(*,
'(a,i0,a)')
'Maximum number of iterations ( ',maxiter,
' ) exceeded'
387 write(*,
'(a,1pg10.3,a,i0)')
'Time = ', time,
' Number of time iterations = ', itime
411 (coreprof_old, coreprof_iter, coreprof_new, &
412 equilibrium_old, equilibrium_iter, &
413 coretransp, coresource, coreimpur, &
414 control_integer, control_double, ets_parameters)
445 CALL deallocate_cpo(coreprof_iter )
446 CALL copy_cpo(coreprof_new,coreprof_iter)
448 CALL deallocate_cpo(coreprof_new )
457 write(*,*)
'Convergence test: ', iter, control_double(4), control_double(5)
459 IF (control_double(4).GT.control_double(5)) goto 10
466 CALL
write_out(itime,coreprof_iter, coreprof_analytic)
469 if(shot_no.gt.0.and.run_no.ge.0)
then
471 coreprof_iter(1)%time=time
473 write(*,*)
'euitm_put_non_timed: coreprof', coreprof_iter(1)%time, &
474 trim(coreprof_iter(1)%codeparam%codename(1)), &
476 trim(coreprof_iter(1)%codeparam%codeversion(1))
477 call euitm_put_non_timed(idx,
"coreprof",coreprof_iter(1))
479 write(*,*)
'euitm_put_slice: coreprof', coreprof_iter(1)%time
480 call euitm_put_slice(idx,
"coreprof",coreprof_iter(1))
481 equilibrium_iter(1)%time=time
482 write(*,*)
'euitm_put_slice: equilibrium', equilibrium_iter(1)%time
483 call euitm_put_slice(idx,
"equilibrium",equilibrium_iter(1))
484 coretransp(1)%time=time
485 write(*,*)
'euitm_put_slice: coretransp', coretransp(1)%time
486 call euitm_put_slice(idx,
"coretransp",coretransp(1))
487 coresource(1)%time=time
488 write(*,*)
'euitm_put_slice: coresource', coresource(1)%time
489 call euitm_put_slice(idx,
"coresource",coresource(1))
490 coreprof_analytic(1)%time=time
491 write(*,*)
'euitm_put_slice: coreprof/1', coreprof_analytic(1)%time
492 call euitm_put_slice(idx,
"coreprof/1",coreprof_analytic(1))
508 CALL deallocate_cpo(coreprof_old )
509 call copy_cpo(coreprof_iter,coreprof_old)
510 CALL deallocate_cpo(coreprof_iter )
511 CALL deallocate_cpo(equilibrium_old )
512 call copy_cpo(equilibrium_iter,equilibrium_old)
513 CALL deallocate_cpo(equilibrium_iter )
514 CALL deallocate_cpo(coreprof_analytic)
515 CALL deallocate_cpo(coretransp )
516 CALL deallocate_cpo(coresource )
517 CALL deallocate_cpo(coreimpur )
535 CALL deallocate_cpo(equilibrium_old )
536 CALL deallocate_cpo(coreprof_old )
537 call deallocate_cpo(code_parameters )
538 call deallocate_cpo(ets_parameters )
543 if(shot_no.gt.0.and.run_no.ge.0)
then
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
program solver_test
This routine aimed in testing the solver solution method for the set of transport equations with give...
Module provides routines for copying parts of CPOs (COREPROF and EQUILIBRIUM)
subroutine write_out(ITIME, COREPROF_NEW, COREPROF_ANALYTIC)
This subroutine stores the results of computations into files.
subroutine check_convergence(COREPROF_ITER, COREPROF_NEW, CONTROL_DOUBLE)
Convergence check This routine checks the convergence of plasma profiles.
subroutine itm_ets(COREPROF_OLD, COREPROF_ITER, COREPROF_NEW, EQUILIBRIUM_OLD, EQUILIBRIUM_ITER, CORETRANSP, CORESOURCE, COREIMPUR, CONTROL_INTEGER, CONTROL_DOUBLE, code_parameters)
ETS.
subroutine allocate_coreprof_cpo(NSLICE, NRHO, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP, COREPROF)
This routine allocates COREPROF CPO.
subroutine allocate_run_control(CONTROL, ifail)
Allocate parameters required by the run control and iterations loop.
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 set_control(SOLVER_TYPE, SIGMA_SOURCE, TAU, AMIX, CONVREC, CONTROL)
setup control structure
subroutine set_plasma_composition(COREPROF_OUT, NION, NIMP, NNEUT, AMN_ION, ZN_ION, Z_ION, AMN_IMP, ZN_IMP, MAXZ_IMP, NCOMP_IN, NTYPE_IN, NCOLD, NTHERMAL, NFAST, NNBI)
subroutine analyticalplasma(TIME, COREPROF_in, EQUILIBRIUM, COREPROF, CORETRANSP, CORESOURCE, COREIMPUR, code_parameters)
Module to cope with problems in fc2k.
The module declares types of variables used in ETS (transport code)
subroutine copy_boundary_cond(COREPROF_IN, COREPROF_OUT)
subroutine analytical_plasma(TIME, COREPROF_in, EQUILIBRIUM, COREPROF_ANALYTIC, CORETRANSP, CORESOURCE, COREIMPUR, code_parameters)
This routine manufactures the solution for the set of transport equations describing the main plasma...
Module provides the convergence check for the ETS.
subroutine euitm_close(idx)
Module for manufacture of a test case for the ETS.