ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
ets_plasma.f90
Go to the documentation of this file.
1 !--------------------------------------------------------
7 !--------------------------------------------------------
8 MODULE ets_plasma
9 !--------------------------------------------------------
10 ! The module declares types of variables !
11 ! used in ETS (transport code) !
12 !--------------------------------------------------------
13  USE itm_types
14  IMPLICIT NONE
15 
16 
17 
18 
19 !--------------------------------------------------------
20 !--------------------------------------------------------
22 
23  REAL (R8), POINTER :: CURRENT !plasma total current
24  REAL (R8), POINTER :: CURRENT_NI !plasma total non-inductive current
25  REAL (R8), POINTER :: VLOOP !loop voltage
26  REAL (R8), POINTER :: LI !internal inductance
27  REAL (R8), POINTER :: BETA_N !beta normalized
28  REAL (R8), POINTER :: BETA_TOR !beta toroidal
29  REAL (R8), POINTER :: BETA_POL !beta poloidal
30  REAL (R8), POINTER :: WDIA !plasma storred energy
31  REAL (R8), POINTER :: QOH !plasma storred energy
32 
33 
34  END TYPE global_param
35 !--------------------------------------------------------
36 !--------------------------------------------------------
37 
38 
39 
40 
41 
42 !--------------------------------------------------------
43 !--------------------------------------------------------
45 
46  INTEGER :: NRHO !number of radial points
47 
48 ! + + radius dependent:
49  REAL (R8), POINTER :: &
50  RHO(:), & !radial coordinate array
51  RHO_NORM(:), & !normalized radial coordinate array
52  HRHO(:), & !intervals between radial knots, hrho(i)=rho(i+1)-rho(i)
53  VPR(:), & !volume derivative, V'
54  VPRM(:), & !volume derivative, V' (time step "-1")
55  G1(:), & !geometry coefficient, <[nabla_RHO]^2>
56  G2(:), & !geometry coefficient, <R>
57  G2M(:), & !geometry coefficient, <R> (time step "-1")
58  G3(:), & !geometry coefficient, <[nabla_RHO/R]^2>
59  G3M(:), & !geometry coefficient, <[nabla_RHO/R]^2> (time step "-1")
60  FDIA(:), & !diamagnetic function
61 ! + + radius independent:
62  r0, & !major radius at which B0 is defined
63  b0, & !magnetic field
64  rgeo, & !major radius of LCMS centre
65  bgeo, & !magnetic field at RGEO
66  bgeom, & !magnetic field at RGEO
67  rho_bnd, & !boundary value of rho_tor
68  rho_bnd_prime, & !time derivative of rho_tor boundary value
69  phi_bnd, & !boundary value of toroidal flux
70  phi_bnd_prime !time derivative of toroidal flux boundary value
71 
72  END TYPE magnetic_geometry
73 !--------------------------------------------------------
74 !--------------------------------------------------------
75 
76 
77 
78 !--------------------------------------------------------
79 !--------------------------------------------------------
81 
82 ! + + Dimensions:
83  INTEGER :: NRHO !number of radial points
84  INTEGER :: NION !number of ion species
85 
86  INTEGER :: SIGMA_SOURCE !source of sigma
87 
88 ! + + Boundary conditions:
89  INTEGER, POINTER :: PSI_BND_TYPE !PSI, type of boundary conditions (boundary dependent)
90  REAL (R8), POINTER :: PSI_BND_RHO !PSI, type of boundary conditions (boundary dependent)
91  REAL (R8), POINTER :: PSI_BND(:) !PSI, boundary conditions (value), (boundary and boundary type dependent)
92 
93  INTEGER, POINTER :: NE_BND_TYPE !NE, type of boundary conditions (boundary and ion type dependent)
94  REAL (R8), POINTER :: NE_BND_RHO !NE, boundary conditions radius
95  REAL (R8), POINTER :: NE_BND(:) !NE, boundary conditions (value), (boundary, boundary type and ion type dependent)
96 
97  INTEGER, POINTER :: NI_BND_TYPE(:) !NI, type of boundary conditions (boundary and ion type dependent)
98  REAL (R8), POINTER :: NI_BND_RHO(:) !NI, boundary conditions radius
99  REAL (R8), POINTER :: NI_BND(:,:) !NI, boundary conditions (value), (boundary, boundary type and ion type dependent)
100 
101  INTEGER, POINTER :: TI_BND_TYPE(:) !TI, type of boundary conditions (boundary and ion type dependent)
102  REAL (R8), POINTER :: TI_BND_RHO(:) !TI, boundary conditions radius
103  REAL (R8), POINTER :: TI_BND(:,:) !TI, boundary conditions (value), (boundary, boundary type and ion type dependent)
104 
105  INTEGER, POINTER :: TE_BND_TYPE !TE, type of boundary conditions, (boundary dependent)
106  REAL (R8), POINTER :: TE_BND_RHO !TE, boundary conditions radius
107  REAL (R8), POINTER :: TE_BND(:) !TE, boundary conditions (value), (boundary and boundary type dependent)
108 
109  INTEGER, POINTER :: VTOR_BND_TYPE(:) !VTOR, type of boundary conditions (boundary and ion type dependent)
110  REAL (R8), POINTER :: VTOR_BND_RHO(:) !VTOR, boundary conditions radius
111  REAL (R8), POINTER :: VTOR_BND(:,:) !VTOR, boundary conditions (value), (boundary, boundary type and ion type dependent)
112 
113  REAL (R8), POINTER :: &
114 
115 ! + + Plasma composition:
116 ! (ion type dependent):
117  zion(:), & !ion charge
118  zion2(:), & !ion charge squared
119  mion(:), & !ion mass number
120 !
121 ! + + parameters linked with current equations:
122 ! (radius dependent):
123  psi(:), & !poloidal magnetic flux function
124  dpsi(:), & !poloidal magnetic flux function derivative
125  psim(:), & !poloidal magnetic flux function (time step "-1")
126  dpsim(:), & !poloidal magnetic flux function derivative (time step "-1")
127  phi(:), & !toroidal magnetic flux function
128  qsf(:), & !safety factor (calculated)
129  curr_tor(:), & !density of toroidal current
130  curr_par(:), & !density of parallel current
131  e_par(:), & !density of parallel current
132  pr(:), & !total pressure
133  sigma(:), & !conductivity
134  jni(:), & !non-inductive current
135  qoh(:), & !Ohmic heating
136  int_qoh(:), & !the integral of Ohmic heating
137  joh(:), & !Ohmic current
138  vloop(:), & !loop voltage
139  shear(:), & !magnetic shear
140  bpol(:), & !poloidal magnetic field
141 !
142 ! + + density and fluxes of all ion components:
143 ! (radius and ion type dependent):
144  ni(:,:), & !ion density (calculated)
145  dni(:,:), & !ion density (calculated) derivative
146  nim(:,:), & !ion density (calculated) (time step "-1")
147  dnim(:,:), & !ion density (calculated) derivative (time step "-1")
148  flux_ni(:,:), & !ion particle flux
149  contrib_2_energy_flux_ni(:,:), & !ion particle flux contributing to heat transport
150  flux_ni_conv(:,:), & !ion particle flux contributing to heat transport
151  int_source_ni(:,:), & !ion particle flux determined from the integral of sources
152  diff_ni(:,:), & !ion particle diffusion
153  vconv_ni(:,:), & !ion particle pinch velocity
154  source_ni(:,:), & !ion particle sources
155  ni_fast(:,:), & !non-thermal ion density
156 !
157 ! + + electron density and flux:
158 ! (radius dependent):
159  ne(:), & !electron density
160  dne(:), & !electron density derivative
161  nem(:), & !electron density (time step "-1")
162  dnem(:), & !electron density derivative (time step "-1")
163  flux_ne(:), & !electron flux
164  contrib_2_energy_flux_ne(:), & !electron flux contributing to heat transport
165  flux_ne_conv(:), & !electron flux contributing to heat transport
166  int_source_ne(:), & !electron particle flux determined from the integral of sources
167  diff_ne(:), & !effective particle diffusion
168  vconv_ne(:), & !effective particle pinch velocity
169  source_ne(:), & !effective particle sources
170  ne_fast(:), & !non-thermal electron density
171 !
172  zeff(:), & !effective charge
173 !
174 ! + + temperature and heat fluxes of all ion components:
175 ! (radius and ion type dependent):
176  ti(:,:), & !ion temperature (calculated)
177  dti(:,:), & !ion temperature (calculated) derivative
178  tim(:,:), & !ion temperature (calculated) (time step "-1")
179  dtim(:,:), & !ion temperature (calculated) derivative (time step "-1")
180  flux_ti(:,:), & !total ion heat flux
181  flux_ti_cond(:,:), & !conductive ion heat flux
182  flux_ti_conv(:,:), & !convective ion heat flux
183  int_source_ti(:,:), & !ion heat flux determined from the integral of sources
184  diff_ti(:,:), & !ion heat diffusion
185  vconv_ti(:,:), & !ion heat pinch velocity
186  source_ti(:,:), & !ion heat sources
187  pi(:,:), & !total ion pressure
188  pi_fast(:,:), & !non-thermal ion pressure
189 !
190 ! + + electron temperature and heat flux:
191 ! (radius dependent):
192  te(:), & !electron temperature (calculated)
193  dte(:), & !electron temperature (calculated) derivative
194  tem(:), & !electron temperature (calculated) (time step "-1")
195  dtem(:), & !electron temperature (calculated) derivative (time step "-1")
196  flux_te(:), & !total electron heat flux
197  flux_te_cond(:), & !conductive electron heat flux
198  flux_te_conv(:), & !convective electron heat flux
199  int_source_te(:), & !electron heat flux determined from the integral of sources
200  diff_te(:), & !electron heat diffusion
201  vconv_te(:), & !electron heat pinch velocity
202  source_te(:), & !electron heat sources
203  pe(:), & !total electron pressure
204  pe_fast(:), & !non-thermal pressure
205 !
206 ! + + toroidal momentum and rotation velocity:
207 ! (radius and ion type dependent):
208  wtor(:,:), & !angular toroidal frequency (only propagated)
209  vtor(:,:), & !ion toroidal velocity (calculated)
210  dvtor(:,:), & !ion toroidal velocity (calculated) derivative
211  vtorm(:,:), & !ion toroidal velocity (calculated) (time step "-1")
212  dvtorm(:,:), & !ion toroidal velocity (calculated) derivative (time step "-1")
213  mtor(:,:), & !ion toridal momentun
214  mtor_tot(:), & !total ion toridal momentun
215  flux_mtor(:,:), & !toroidal momentum flux
216  flux_mtor_conv(:,:), & !convective contribution to toroidal momentum flux
217  flux_mtor_cond(:,:), & !conductive contribution to toroidal momentum flux
218  flux_mtor_tot(:), & !total toroidal momentum flux
219  int_source_mtor(:,:), & !ion momentum flux determined from the integral of sources
220  diff_vtor(:,:), & !ion rotation diffusion
221  vconv_vtor(:,:), & !ion rotation pinch velocity
222  source_mtor(:,:), & !ion momentum sources
223 !
224 ! + + other plasma parameters (external):
225 ! (radius and ion type dependent):
226  vpol(:,:), & !poloidal velocity of ions
227  kneo(:,:), & !neoclassical coefficient, K
228  qei_out(:) !collisional heat transfer electons_ions (total)
229  END TYPE plasma_profiles
230 !--------------------------------------------------------
231 !--------------------------------------------------------
232 
233 
234 
235 !--------------------------------------------------------
236 !--------------------------------------------------------
238 
239  INTEGER :: NRHO !number of radial points
240  INTEGER :: NION !number of ion species
241  INTEGER, POINTER :: SIGMA_SOURCE !the source for plasma resistance (ETS/NCLASS)
242 
243  REAL (R8), POINTER :: &
244 !
245 ! + + current transport:
246 ! (radius and model dependent):
247  sigma(:), & !plasma parallel conductivity
248 !
249 ! + + electron particle transport coefficients
250 ! (radius, ion type and model dependent):
251  diff_ne(:,:), & !partical diffusion
252  vconv_ne(:,:), & !particle pinch velocity
253 ! DIFF_NE(:), & !partical diffusion
254 ! VCONV_NE(:), & !particle pinch velocity
255  diff_ne_model(:,:), & !partical diffusion
256  vconv_ne_model(:,:), & !particle pinch velocity
257 !
258 ! + + ion particle transport coefficients
259 ! (radius, ion type and model dependent):
260  diff_ni(:,:,:), & !partical diffusion
261  vconv_ni(:,:,:), & !particle pinch velocity
262 ! DIFF_NI(:,:), & !partical diffusion
263 ! VCONV_NI(:,:), & !particle pinch velocity
264  diff_ni_model(:,:,:), & !partical diffusion
265  vconv_ni_model(:,:,:), & !particle pinch velocity
266 !
267 ! + + ion heat transport coefficients
268 ! (model dependent):
269  c1(:), & !coefficient in front of convective flux
270 ! (radius, ion type and model dependent):
271  diff_ti(:,:), & !ion heat diffusion
272  vconv_ti(:,:), & !ion heat pinch velocity
273  qgi(:,:), & !flow energy exchange term in RHS of eq.
274 !
275 ! + + electron heat transport coefficients
276 ! (radius and model dependent):
277  diff_te(:), & !electron heat diffusion
278  vconv_te(:), & !electron heat pinch velocity
279  qge(:), & !flow energy exchange term in RHS of eq.
280 !
281 ! + + ion velocity transport coefficients
282 ! (radius, ion type and model dependent):
283  diff_vtor(:,:), & !diffusion coefficient for ion velocity
284  vconv_vtor(:,:) !pinch velocity for ion velocity
285 
286  END TYPE transport_coefficients
287 !--------------------------------------------------------
288 !--------------------------------------------------------
289 
290 
291 
292 !--------------------------------------------------------
293 !--------------------------------------------------------
295 
296  INTEGER :: NRHO !number of radial points
297  INTEGER :: NION !number of ion species
298 
299  REAL (R8), POINTER :: &
300 !
301 ! + + current transport:
302 ! (radius dependent):
303  sigma(:), & !plasma parallel conductivity
304 ! (radius dependent):
305  curr_exp(:), & !non inductive current, explicit component
306  curr_imp(:), & !non inductive current, implicit component
307 !
308 ! +++ electron particle sources
309 ! (radius and ion type dependent):
310  se_exp(:), & !external ion sources, explicit component
311  se_imp(:), & !external ion sources, implicit component
312 !
313 ! +++ ion particle sources
314 ! (radius and ion type dependent):
315  si_exp(:,:), & !external ion sources, explicit component
316  si_imp(:,:), & !external ion sources, implicit component
317 !
318 ! +++ ion heat sources
319 ! (radius and ion type dependent):
320  qi_exp(:,:), & !external ion heat sources, explicit component
321  qi_imp(:,:), & !external ion heat sources, implicit component
322 !
323 ! +++ electron heat sources
324 ! (radius dependent):
325  qoh(:), & !ohmic heating
326  qe_exp(:), & !external electron heat sources, explicit component
327  qe_imp(:), & !external electron heat sources, implicit component
328 !
329 ! +++ ion momentum sources
330 ! (radius and ion type dependent):
331  ui_exp(:,:), & !external ion momentum sources, explicit component
332  ui_imp(:,:) !external ion momentum sources, implicit component
333 
334 
335  END TYPE sources_and_sinks
336 !--------------------------------------------------------
337 !--------------------------------------------------------
338 
339 
340 
341 !--------------------------------------------------------
342 !--------------------------------------------------------
344 
345  INTEGER :: NRHO !number of radial points
346  INTEGER :: NION !number of ion species
347 
348  REAL (R8), POINTER :: &
349 !
350 ! +++ various exchange components:
351 ! (radius and ion type dependent):
352  sigma(:), & !plasma parallel conductivity
353  vzi(:,:), & !ion energy exchange to other ions, implicit (frequency)
354  qzi(:,:), & !ion energy exchange to other ions, explicit
355  vei(:,:), & !ion energy exchange to electrons, implicit (frequency)
356  qei(:,:), & !ion energy exchange to electrons, explicit
357  wzi(:,:), & !ion momentum exchange to other ions, implicit
358  uzi(:,:), & !ion momentum exchange to other ions, explicit
359  vie(:), & !electron energy exchange to ions, implicit (frequency)
360  qie(:), & !electron energy exchange to ions, explicit
361  vii(:,:,:), & !ion-ion collision frequency (matrix)
362  wii(:,:,:) !ion-ion momentum exchange (matrix)
363 
364 
365  END TYPE collisionality
366 !--------------------------------------------------------
367 !--------------------------------------------------------
368 
369 
370 
371 !--------------------------------------------------------
372 !--------------------------------------------------------
374 
375  INTEGER :: NRHO !number of radial points
376  INTEGER :: NIMP !number of impurity species
377  INTEGER :: NZIMP !maximum number of ionization states
378 
379  REAL (R8), POINTER :: &
380 ! + + density and fluxes of impurities:
381 ! (radius and impurity ion type dependent):
382  nz(:,:,:), & !density
383  flux_nz(:,:,:), & !flux
384  zimp(:,:,:), & !impurity charge
385  zimp2(:,:,:) !impurity charge squared
386 
387  END TYPE impurity_profiles
388 !--------------------------------------------------------
389 !--------------------------------------------------------
390 
391 
392 
393 !--------------------------------------------------------
394 !--------------------------------------------------------
396 
397  INTEGER :: NRHO !number of radial points
398  INTEGER :: NION !number of ion species
399 
400  REAL (R8), POINTER :: &
401  PSIM(:), & !flux function at previous time step
402  DPSIM(:), & !flux function at previous time step derivative, AF - 25.Sep.2014
403  NIM(:,:), & !ion density at previous time step
404  DNIM(:,:), & !ion density at previous time step derivative, AF - 25.Sep.2014
405  TIM(:,:), & !ion temperature at previous time step
406  DTIM(:,:), & !ion temperature at previous time step derivative, AF - 25.Sep.2014
407  NEM(:), & !electron density at previous time step
408  DNEM(:), & !electron density at previous time step derivative, AF - 25.Sep.2014
409  TEM(:), & !electron temperature at previous time step
410  DTEM(:), & !electron temperature at previous time step derivative, AF - 25.Sep.2014
411  VTORM(:,:), & !ion toroidal velocity at previous time step
412  DVTORM(:,:), & !ion toroidal velocity at previous time step derivative, AF - 25.Sep.2014
413  VPRM(:), & !V' at previous time step
414  G2M(:), & !<R> at previous time step
415  G3M(:), & !<[nabla_RHO/R]^2> at previous time step
416  BTM !toroidal magnetic field at previous time step
417 
418  END TYPE time_evolution
419 !--------------------------------------------------------
420 !--------------------------------------------------------
421 
422 
423 
424 !--------------------------------------------------------
425 !--------------------------------------------------------
427 
428  INTEGER :: SOLVER_TYPE !options for numerical solver
429  !1-"standard" RITM;
430  !2-"integral" RITM;
431  !3-"PROGONKA"
432 
433  INTEGER :: SIGMA_SOURCE !option for origin of Plasma electrical conductivity
434  !0: plasma collisions
435  !1: transport module
436  !2: source module
437 
438 
439  INTEGER :: QUASI_NEUT !option for origin of Plasma electrical conductivity
440  !0: electrons
441  !1: ions from BC: ni1/ni1_bnd=ni2/ni2_bnd=...
442  !2: ions from carge: ni1*Z1=ni2*Z2=...
443 
444  INTEGER :: DEBUG_LEVEL
445 
446  REAL (R8) :: ohmic_heating_multiplier
447 
448  REAL (R8), POINTER :: &
449  TAU, & !time step
450  AMIX, & !mixing factor for profile
451  AMIXTR, & !mixing factor for transport coefficients
452  CONV, & !actual convergence
453  CONVREC
454 
455  END TYPE run_control
456 !--------------------------------------------------------
457 !--------------------------------------------------------
458 
459 
460 
461 !--------------------------------------------------------
462 !--------------------------------------------------------
464 
465  CHARACTER*1000 :: ERROR_MESSAGE
466  INTEGER :: IERR
467 
468  END TYPE diagnostic
469 !--------------------------------------------------------
470 !--------------------------------------------------------
471 
472 
473 
474 
475 
476 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
477 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
478 CONTAINS
479 
480 
481 
482 
483 
484 !--------------------------------------------------------!
485 ! !
486 ! !
487 ! !
488 ! ALLOCATION OF ETS INTERNAL STRUCTURES !
489 ! !
490 ! !
491 ! !
492 !--------------------------------------------------------!
493 
494 
495 
496 
497 
498 !--------------------------------------------------------!
499 !--------------------------------------------------------!
500 ! ----------------- MAGNETIC GEOMETRY ------------------ !
501 
502  SUBROUTINE allocate_magnetic_geometry (NRHO, GEOMETRY, ifail)
503 
504 ! +++ Input/Output:
505  INTEGER, INTENT (IN) :: nrho
506  TYPE (magnetic_geometry) :: geometry
507  INTEGER, INTENT (INOUT) :: ifail
508 
509 ! +++ Local variables:
510  INTEGER :: istat
511 
512  ALLOCATE (geometry%RHO(nrho), &
513  geometry%RHO_NORM(nrho), &
514  geometry%HRHO(nrho), &
515  geometry%VPR(nrho), &
516  geometry%VPRM(nrho), &
517  geometry%G1(nrho), &
518  geometry%G2(nrho), &
519  geometry%G2M(nrho), &
520  geometry%G3(nrho), &
521  geometry%G3M(nrho), &
522  geometry%FDIA(nrho), &
523  geometry%R0, &
524  geometry%B0, &
525  geometry%RGEO, &
526  geometry%BGEO, &
527  geometry%BGEOM, &
528  geometry%RHO_BND, &
529  geometry%RHO_BND_PRIME, &
530  geometry%PHI_BND, &
531  geometry%PHI_BND_PRIME, &
532  stat=istat)
533 
534 ! +++ Error checking and reporting:
535  IF (istat /= 0) THEN
536  ifail = max(ifail,1) ! Failure to allocate
537  write(*,*) 'ALLOCATE_MAGNETIC_GEOMETRY: Failure to allocate'
538  RETURN
539  ELSE
540  ifail = max(ifail,0) ! Normal return
541  END IF
542 
543 ! +++ Set dimensions
544  geometry%NRHO = nrho
545 
546 ! +++ Zero out arrays
547  geometry%RHO(:) = 0.0_r8
548  geometry%RHO_NORM(:) = 0.0_r8
549  geometry%HRHO(:) = 0.0_r8
550  geometry%VPR(:) = 0.0_r8
551  geometry%VPRM(:) = 0.0_r8
552  geometry%G1(:) = 0.0_r8
553  geometry%G2(:) = 0.0_r8
554  geometry%G2M(:) = 0.0_r8
555  geometry%G3(:) = 0.0_r8
556  geometry%G3M(:) = 0.0_r8
557  geometry%FDIA(:) = 0.0_r8
558  geometry%R0 = 0.0_r8
559  geometry%B0 = 0.0_r8
560  geometry%RGEO = 0.0_r8
561  geometry%BGEO = 0.0_r8
562  geometry%BGEOM = 0.0_r8
563  geometry%RHO_BND = 0.0_r8
564  geometry%RHO_BND_PRIME = 0.0_r8
565  geometry%PHI_BND = 0.0_r8
566  geometry%PHI_BND_PRIME = 0.0_r8
567 
568  END SUBROUTINE allocate_magnetic_geometry
569 !--------------------------------------------------------!
570 !--------------------------------------------------------!
571 
572 
573 !--------------------------------------------------------!
574 !--------------------------------------------------------!
575  SUBROUTINE deallocate_magnetic_geometry (GEOMETRY, ifail)
576 
577 ! +++ Input/Output:
578  TYPE (magnetic_geometry) :: geometry
579  INTEGER, INTENT (INOUT) :: ifail
580 
581 ! +++ Local variables
582  INTEGER :: istat
583 
584  DEALLOCATE (geometry%RHO, &
585  geometry%HRHO, &
586  geometry%RHO_NORM, &
587  geometry%VPR, &
588  geometry%VPRM, &
589  geometry%G1, &
590  geometry%G2, &
591  geometry%G2M, &
592  geometry%G3, &
593  geometry%G3M, &
594  geometry%FDIA, &
595  geometry%R0, &
596  geometry%B0, &
597  geometry%RGEO, &
598  geometry%BGEO, &
599  geometry%BGEOM, &
600  geometry%RHO_BND, &
601  geometry%RHO_BND_PRIME, &
602  geometry%PHI_BND, &
603  geometry%PHI_BND_PRIME, &
604  stat=istat)
605 
606 
607 ! +++ Error checking and reporting
608  IF (istat /= 0) THEN
609  ifail = max(ifail,1) ! Failure to allocate
610  write(*,*) 'DEALLOCATE_MAGNETIC_GEOMETRY: Failure to deallocate'
611  RETURN
612  ELSE
613  ifail = max(ifail,0) ! Normal return
614  END IF
615 
616  END SUBROUTINE deallocate_magnetic_geometry
617 !--------------------------------------------------------!
618 !--------------------------------------------------------!
619 
620 
621 
622 
623 
624 
625 
626 !--------------------------------------------------------!
627 !--------------------------------------------------------!
628 ! -------------- GLOBAL PLASMA PARAMETERS -------------- !
629 
630  SUBROUTINE allocate_global_param (GLOBAL, ifail)
631 
632  TYPE (global_param) :: global
633  INTEGER, INTENT (INOUT) :: ifail
634  INTEGER :: istat
635 
636  ALLOCATE (global%CURRENT, &
637  global%CURRENT_NI, &
638  global%VLOOP, &
639  global%LI, &
640  global%BETA_N, &
641  global%BETA_TOR, &
642  global%BETA_POL, &
643  global%WDIA, &
644  global%QOH, &
645  stat=istat)
646 
647 
648 ! +++ Error checking and reporting
649  IF (istat /= 0) THEN
650  ifail = max(ifail,1) ! Failure to allocate
651  write(*,*) 'DEALLOCATE_MAGNETIC_GEOMETRY: Failure to deallocate'
652  RETURN
653  ELSE
654  ifail = max(ifail,0) ! Normal return
655  END IF
656 
657  global%CURRENT = 0.0_r8
658  global%CURRENT_NI = 0.0_r8
659  global%VLOOP = 0.0_r8
660  global%LI = 0.0_r8
661  global%BETA_N = 0.0_r8
662  global%BETA_TOR = 0.0_r8
663  global%BETA_POL = 0.0_r8
664  global%WDIA = 0.0_r8
665  global%QOH = 0.0_r8
666 
667  RETURN
668 
669  END SUBROUTINE allocate_global_param
670 !--------------------------------------------------------
671 !--------------------------------------------------------
672 
673 
674 
675 !--------------------------------------------------------
676 !--------------------------------------------------------
677  SUBROUTINE deallocate_global_param (GLOBAL, ifail)
678 
679  TYPE (global_param) :: global
680  INTEGER, INTENT (INOUT) :: ifail
681  INTEGER :: istat
682 
683  DEALLOCATE (global%CURRENT, &
684  global%CURRENT_NI, &
685  global%VLOOP, &
686  global%LI, &
687  global%BETA_N, &
688  global%BETA_TOR, &
689  global%BETA_POL, &
690  global%WDIA, &
691  global%QOH, &
692  stat=istat)
693 
694 
695 ! +++ Error checking and reporting
696  IF (istat /= 0) THEN
697  ifail = max(ifail,1) ! Failure to allocate
698  write(*,*) 'DEALLOCATE_MAGNETIC_GEOMETRY: Failure to deallocate'
699  RETURN
700  ELSE
701  ifail = max(ifail,0) ! Normal return
702  END IF
703 
704 
705  RETURN
706 
707  END SUBROUTINE deallocate_global_param
708 !--------------------------------------------------------
709 !--------------------------------------------------------
710 
711 
712 
713 !--------------------------------------------------------!
714 !--------------------------------------------------------!
715 ! ------------------ PLASMA PROFILES ------------------- !
716 
717  SUBROUTINE allocate_plasma_profiles (NRHO, NION, PROFILES, ifail)
718 
719 ! +++ Input/Output:
720  INTEGER, INTENT (IN) :: nrho, nion
721  TYPE (plasma_profiles) :: profiles
722  INTEGER, INTENT (INOUT) :: ifail
723 
724 ! +++ Local variables:
725  INTEGER :: istat
726 
727  ALLOCATE (profiles%ZION(nion), &
728  profiles%ZION2(nion), &
729  profiles%MION(nion), &
730 !
731  profiles%PSI(nrho), &
732  profiles%DPSI(nrho), &
733  profiles%PSIM(nrho), &
734  profiles%DPSIM(nrho), &
735  profiles%PHI(nrho), &
736  profiles%QSF(nrho), &
737  profiles%CURR_TOR(nrho), &
738  profiles%CURR_PAR(nrho), &
739  profiles%E_PAR(nrho), &
740  profiles%PR(nrho), &
741  profiles%SIGMA(nrho), &
742  profiles%JNI(nrho), &
743  profiles%QOH(nrho), &
744  profiles%INT_QOH(nrho), &
745  profiles%JOH(nrho), &
746  profiles%VLOOP(nrho), &
747  profiles%SHEAR(nrho), &
748  profiles%BPOL(nrho), &
749 !
750  profiles%PSI_BND(3), &
751  profiles%PSI_BND_TYPE, &
752  profiles%PSI_BND_RHO, &
753 !
754  profiles%NI(nrho,nion), &
755  profiles%DNI(nrho,nion), &
756  profiles%NIM(nrho,nion), &
757  profiles%DNIM(nrho,nion), &
758  profiles%FLUX_NI(nrho,nion), &
759  profiles%FLUX_NI_CONV(nrho,nion), &
760  profiles%CONTRIB_2_ENERGY_FLUX_NI(nrho,nion), &
761  profiles%INT_SOURCE_NI(nrho,nion), &
762  profiles%NI_BND(3,nion), &
763  profiles%NI_BND_TYPE(nion), &
764  profiles%NI_BND_RHO(nion), &
765  profiles%DIFF_NI(nrho,nion), &
766  profiles%VCONV_NI(nrho,nion), &
767  profiles%SOURCE_NI(nrho,nion), &
768  profiles%NI_FAST(nrho,nion), &
769 !
770  profiles%NE(nrho), &
771  profiles%DNE(nrho), &
772  profiles%NEM(nrho), &
773  profiles%DNEM(nrho), &
774  profiles%FLUX_NE(nrho), &
775  profiles%FLUX_NE_CONV(nrho), &
776  profiles%CONTRIB_2_ENERGY_FLUX_NE(nrho), &
777  profiles%INT_SOURCE_NE(nrho), &
778  profiles%NE_BND(3), &
779  profiles%NE_BND_TYPE, &
780  profiles%NE_BND_RHO, &
781  profiles%ZEFF(nrho), &
782  profiles%DIFF_NE(nrho), &
783  profiles%VCONV_NE(nrho), &
784  profiles%SOURCE_NE(nrho), &
785  profiles%NE_FAST(nrho), &
786 !
787  profiles%TI(nrho,nion), &
788  profiles%DTI(nrho,nion), &
789  profiles%TIM(nrho,nion), &
790  profiles%DTIM(nrho,nion), &
791  profiles%FLUX_TI(nrho,nion), &
792  profiles%FLUX_TI_COND(nrho,nion), &
793  profiles%FLUX_TI_CONV(nrho,nion), &
794  profiles%INT_SOURCE_TI(nrho,nion), &
795  profiles%TI_BND(3,nion), &
796  profiles%TI_BND_TYPE(nion), &
797  profiles%TI_BND_RHO(nion), &
798  profiles%DIFF_TI(nrho,nion), &
799  profiles%VCONV_TI(nrho,nion), &
800  profiles%SOURCE_TI(nrho,nion), &
801  profiles%PI(nrho,nion), &
802  profiles%PI_FAST(nrho,nion), &
803 !
804  profiles%TE(nrho), &
805  profiles%DTE(nrho), &
806  profiles%TEM(nrho), &
807  profiles%DTEM(nrho), &
808  profiles%FLUX_TE(nrho), &
809  profiles%FLUX_TE_COND(nrho), &
810  profiles%FLUX_TE_CONV(nrho), &
811  profiles%INT_SOURCE_TE(nrho), &
812  profiles%TE_BND(3), &
813  profiles%TE_BND_RHO, &
814  profiles%TE_BND_TYPE, &
815  profiles%DIFF_TE(nrho), &
816  profiles%VCONV_TE(nrho), &
817  profiles%SOURCE_TE(nrho), &
818  profiles%PE(nrho), &
819  profiles%PE_FAST(nrho), &
820 !
821  profiles%VTOR(nrho,nion), &
822  profiles%DVTOR(nrho,nion), &
823  profiles%VTORM(nrho,nion), &
824  profiles%DVTORM(nrho,nion), &
825  profiles%WTOR(nrho,nion), &
826  profiles%MTOR(nrho,nion), &
827  profiles%MTOR_TOT(nrho), &
828  profiles%FLUX_MTOR(nrho,nion), &
829  profiles%FLUX_MTOR_CONV(nrho,nion), &
830  profiles%FLUX_MTOR_COND(nrho,nion), &
831  profiles%FLUX_MTOR_TOT(nrho), &
832  profiles%INT_SOURCE_MTOR(nrho,nion), &
833  profiles%VTOR_BND(3,nion), &
834  profiles%VTOR_BND_TYPE(nion), &
835  profiles%VTOR_BND_RHO(nion), &
836  profiles%DIFF_VTOR(nrho,nion), &
837  profiles%VCONV_VTOR(nrho,nion), &
838  profiles%SOURCE_MTOR(nrho,nion), &
839 !
840  profiles%VPOL(nrho,nion), &
841  profiles%KNEO(nrho,nion), &
842  profiles%QEI_OUT(nrho), &
843 !
844  stat=istat)
845 
846 ! +++ Error checking and reporting:
847  IF (istat /= 0) THEN
848  ifail = max(ifail,1) ! Failure to allocate
849  write(*,*) 'ALLOCATE_PLASMA_PROFILES: Failure to allocate'
850  RETURN
851  ELSE
852  ifail = max(ifail,0) ! Normal return
853  END IF
854 
855 ! +++ Set dimensions
856  profiles%NRHO = nrho
857  profiles%NION = nion
858 
859  profiles%SIGMA_SOURCE = -1
860 
861 ! +++ Plasma composition:
862  profiles%ZION(:) = 0.0_r8
863  profiles%ZION2(:) = 0.0_r8
864  profiles%MION(:) = 0.0_r8
865 
866 ! +++ Zero out arrays:
867  profiles%PSI(:) = 0.0_r8
868  profiles%DPSI(:) = 0.0_r8
869  profiles%PSIM(:) = 0.0_r8
870  profiles%DPSIM(:) = 0.0_r8
871  profiles%PHI(:) = 0.0_r8
872  profiles%QSF(:) = 0.0_r8
873  profiles%CURR_TOR(:) = 0.0_r8
874  profiles%CURR_PAR(:) = 0.0_r8
875  profiles%E_PAR(:) = 0.0_r8
876  profiles%PR(:) = 0.0_r8
877  profiles%SIGMA(:) = 0.0_r8
878  profiles%JNI(:) = 0.0_r8
879  profiles%QOH(:) = 0.0_r8
880  profiles%INT_QOH(:) = 0.0_r8
881  profiles%JOH(:) = 0.0_r8
882  profiles%VLOOP(:) = 0.0_r8
883  profiles%SHEAR(:) = 0.0_r8
884  profiles%BPOL(:) = 0.0_r8
885 
886  profiles%PSI_BND(:) = 0.0_r8
887  profiles%PSI_BND_TYPE = 0
888  profiles%PSI_BND_RHO = 0.0_r8
889 
890  profiles%NI(:,:) = 0.0_r8
891  profiles%DNI(:,:) = 0.0_r8
892  profiles%NIM(:,:) = 0.0_r8
893  profiles%DNIM(:,:) = 0.0_r8
894  profiles%FLUX_NI(:,:) = 0.0_r8
895  profiles%FLUX_NI_CONV(:,:) = 0.0_r8
896  profiles%CONTRIB_2_ENERGY_FLUX_NI(:,:)= 0.0_r8
897  profiles%INT_SOURCE_NI(:,:) = 0.0_r8
898  profiles%NI_BND(:,:) = 0.0_r8
899  profiles%NI_BND_TYPE(:) = 0
900  profiles%NI_BND_RHO(:) = 0.0_r8
901  profiles%DIFF_NI(:,:) = 0.0_r8
902  profiles%VCONV_NI(:,:) = 0.0_r8
903  profiles%SOURCE_NI(:,:) = 0.0_r8
904  profiles%NI_FAST(:,:) = 0.0_r8
905 
906  profiles%NE(:) = 0.0_r8
907  profiles%DNE(:) = 0.0_r8
908  profiles%NEM(:) = 0.0_r8
909  profiles%DNEM(:) = 0.0_r8
910  profiles%FLUX_NE(:) = 0.0_r8
911  profiles%FLUX_NE_CONV(:) = 0.0_r8
912  profiles%CONTRIB_2_ENERGY_FLUX_NE(:) = 0.0_r8
913  profiles%INT_SOURCE_NE(:) = 0.0_r8
914  profiles%NE_BND(:) = 0.0_r8
915  profiles%NE_BND_TYPE = 0
916  profiles%NE_BND_RHO = 0.0_r8
917  profiles%ZEFF(:) = 1.0_r8
918  profiles%DIFF_NE(:) = 0.0_r8
919  profiles%VCONV_NE(:) = 0.0_r8
920  profiles%SOURCE_NE(:) = 0.0_r8
921  profiles%NE_FAST(:) = 0.0_r8
922 
923  profiles%TI(:,:) = 0.0_r8
924  profiles%DTI(:,:) = 0.0_r8
925  profiles%TIM(:,:) = 0.0_r8
926  profiles%DTIM(:,:) = 0.0_r8
927  profiles%FLUX_TI(:,:) = 0.0_r8
928  profiles%FLUX_TI_COND(:,:) = 0.0_r8
929  profiles%FLUX_TI_CONV(:,:) = 0.0_r8
930  profiles%INT_SOURCE_TI(:,:) = 0.0_r8
931  profiles%TI_BND(:,:) = 0.0_r8
932  profiles%TI_BND_TYPE(:) = 0
933  profiles%TI_BND_RHO(:) = 0.0_r8
934  profiles%DIFF_TI(:,:) = 0.0_r8
935  profiles%VCONV_TI(:,:) = 0.0_r8
936  profiles%SOURCE_TI(:,:) = 0.0_r8
937  profiles%PI(:,:) = 0.0_r8
938  profiles%PI_FAST(:,:) = 0.0_r8
939 
940  profiles%TE(:) = 0.0_r8
941  profiles%DTE(:) = 0.0_r8
942  profiles%TEM(:) = 0.0_r8
943  profiles%DTEM(:) = 0.0_r8
944  profiles%FLUX_TE(:) = 0.0_r8
945  profiles%FLUX_TE_COND(:) = 0.0_r8
946  profiles%FLUX_TE_CONV(:) = 0.0_r8
947  profiles%INT_SOURCE_TE(:) = 0.0_r8
948  profiles%TE_BND(:) = 0.0_r8
949  profiles%TE_BND_TYPE = 0
950  profiles%TE_BND_RHO = 0.0_r8
951  profiles%DIFF_TE(:) = 0.0_r8
952  profiles%VCONV_TE(:) = 0.0_r8
953  profiles%SOURCE_TE(:) = 0.0_r8
954  profiles%PE(:) = 0.0_r8
955  profiles%PE_FAST(:) = 0.0_r8
956 
957  profiles%VTOR(:,:) = 0.0_r8
958  profiles%DVTOR(:,:) = 0.0_r8
959  profiles%VTORM(:,:) = 0.0_r8
960  profiles%DVTORM(:,:) = 0.0_r8
961  profiles%WTOR(:,:) = 0.0_r8
962  profiles%MTOR(:,:) = 0.0_r8
963  profiles%MTOR_TOT(:) = 0.0_r8
964  profiles%FLUX_MTOR(:,:) = 0.0_r8
965  profiles%FLUX_MTOR_CONV(:,:) = 0.0_r8
966  profiles%FLUX_MTOR_COND(:,:) = 0.0_r8
967  profiles%FLUX_MTOR_TOT(:) = 0.0_r8
968  profiles%INT_SOURCE_MTOR(:,:) = 0.0_r8
969  profiles%VTOR_BND(:,:) = 0.0_r8
970  profiles%VTOR_BND_TYPE(:) = 0
971  profiles%VTOR_BND_RHO(:) = 0.0_r8
972  profiles%DIFF_VTOR(:,:) = 0.0_r8
973  profiles%VCONV_VTOR(:,:) = 0.0_r8
974  profiles%SOURCE_MTOR(:,:) = 0.0_r8
975 
976  profiles%VPOL(:,:) = 0.0_r8
977  profiles%KNEO(:,:) = 0.0_r8
978  profiles%QEI_OUT(:) = 0.0_r8
979 
980  END SUBROUTINE allocate_plasma_profiles
981 
982 
983 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
984 ! +++ Deallocate plasma profiles needed by the transport solver
985 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
991 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
992  SUBROUTINE deallocate_plasma_profiles (PROFILES, ifail)
993 
994 ! +++ Input/Output:
995  TYPE (plasma_profiles) :: profiles
996  INTEGER, INTENT (INOUT) :: ifail
997 
998 ! +++ Local variables:
999  INTEGER :: istat
1000 
1001  DEALLOCATE (profiles%ZION, &
1002  profiles%ZION2, &
1003  profiles%MION, &
1004 !
1005  profiles%PSI, &
1006  profiles%DPSI, &
1007  profiles%PSIM, &
1008  profiles%DPSIM, &
1009  profiles%PHI, &
1010  profiles%QSF, &
1011  profiles%CURR_TOR, &
1012  profiles%CURR_PAR, &
1013  profiles%E_PAR, &
1014  profiles%PR, &
1015  profiles%SIGMA, &
1016  profiles%PSI_BND_RHO, &
1017  profiles%JNI, &
1018  profiles%QOH, &
1019  profiles%INT_QOH, &
1020  profiles%JOH, &
1021  profiles%VLOOP, &
1022  profiles%SHEAR, &
1023  profiles%BPOL, &
1024 !
1025  profiles%PSI_BND, &
1026  profiles%PSI_BND_TYPE, &
1027 !
1028  profiles%NI, &
1029  profiles%DNI, &
1030  profiles%NIM, &
1031  profiles%DNIM, &
1032  profiles%FLUX_NI, &
1033  profiles%FLUX_NI_CONV, &
1034  profiles%CONTRIB_2_ENERGY_FLUX_NI, &
1035  profiles%INT_SOURCE_NI, &
1036  profiles%NI_BND, &
1037  profiles%NI_BND_TYPE, &
1038  profiles%NI_BND_RHO, &
1039  profiles%DIFF_NI, &
1040  profiles%VCONV_NI, &
1041  profiles%SOURCE_NI, &
1042  profiles%NI_FAST, &
1043 !
1044  profiles%NE, &
1045  profiles%DNE, &
1046  profiles%FLUX_NE, &
1047  profiles%FLUX_NE_CONV, &
1048  profiles%CONTRIB_2_ENERGY_FLUX_NE, &
1049  profiles%INT_SOURCE_NE, &
1050  profiles%NE_BND, &
1051  profiles%NE_BND_TYPE, &
1052  profiles%NE_BND_RHO, &
1053  profiles%ZEFF, &
1054  profiles%DIFF_NE, &
1055  profiles%VCONV_NE, &
1056  profiles%SOURCE_NE, &
1057  profiles%NE_FAST, &
1058 !
1059  profiles%TI, &
1060  profiles%DTI, &
1061  profiles%FLUX_TI, &
1062  profiles%FLUX_TI_COND, &
1063  profiles%FLUX_TI_CONV, &
1064  profiles%INT_SOURCE_TI, &
1065  profiles%TI_BND, &
1066  profiles%TI_BND_TYPE, &
1067  profiles%TI_BND_RHO, &
1068  profiles%DIFF_TI, &
1069  profiles%VCONV_TI, &
1070  profiles%SOURCE_TI, &
1071  profiles%PI, &
1072  profiles%PI_FAST, &
1073 !
1074  profiles%TE, &
1075  profiles%DTE, &
1076  profiles%TEM, &
1077  profiles%DTEM, &
1078  profiles%FLUX_TE, &
1079  profiles%FLUX_TE_COND, &
1080  profiles%FLUX_TE_CONV, &
1081  profiles%INT_SOURCE_TE, &
1082  profiles%TE_BND, &
1083  profiles%TE_BND_TYPE, &
1084  profiles%TE_BND_RHO, &
1085  profiles%DIFF_TE, &
1086  profiles%VCONV_TE, &
1087  profiles%SOURCE_TE, &
1088  profiles%PE, &
1089  profiles%PE_FAST, &
1090 !
1091  profiles%VTOR, &
1092  profiles%DVTOR, &
1093  profiles%VTORM, &
1094  profiles%DVTORM, &
1095  profiles%WTOR, &
1096  profiles%MTOR, &
1097  profiles%MTOR_TOT, &
1098  profiles%FLUX_MTOR, &
1099  profiles%FLUX_MTOR_CONV, &
1100  profiles%FLUX_MTOR_COND, &
1101  profiles%FLUX_MTOR_TOT, &
1102  profiles%INT_SOURCE_MTOR, &
1103  profiles%VTOR_BND, &
1104  profiles%VTOR_BND_TYPE, &
1105  profiles%VTOR_BND_RHO, &
1106  profiles%DIFF_VTOR, &
1107  profiles%VCONV_VTOR, &
1108  profiles%SOURCE_MTOR, &
1109 !
1110  profiles%VPOL, &
1111  profiles%KNEO, &
1112  profiles%QEI_OUT, &
1113 !
1114  stat=istat)
1115 
1116 ! +++ Error checking and reporting
1117  IF (istat /= 0) THEN
1118  ifail = max(ifail,1) ! Failure to allocate
1119  write(*,*) 'DEALLOCATE_PLASMA_PROFILES: Failure to deallocate'
1120  RETURN
1121  ELSE
1122  ifail = max(ifail,0) ! Normal return
1123  END IF
1124 
1125  END SUBROUTINE deallocate_plasma_profiles
1126 
1127 
1128 
1129 
1130 
1131 
1132 ! ----------------------- TRANSPORT_COEFFICIENTS ---------------------- !
1133 
1134 
1135 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1136 ! +++ Allocate profiles of transport coefficients needed by the transport solver
1137 
1138 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1144 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1145  SUBROUTINE allocate_transport_coefficients (NRHO, NION, TRANSPORT, ifail)
1146 
1147 ! +++ Input/Output:
1148  INTEGER, INTENT (IN) :: nrho, nion
1149  TYPE (transport_coefficients) :: transport
1150  INTEGER, INTENT (INOUT) :: ifail
1151 
1152 ! +++ Local variables
1153  INTEGER :: istat
1154 
1155  ALLOCATE (transport%SIGMA_SOURCE, &
1156  transport%SIGMA(nrho), &
1157 !
1158  transport%DIFF_NE(nrho,3), &
1159  transport%VCONV_NE(nrho,3), &
1160 ! TRANSPORT%DIFF_NE(NRHO), &
1161 ! TRANSPORT%VCONV_NE(NRHO), &
1162  transport%DIFF_NE_MODEL(nrho,3), &
1163  transport%VCONV_NE_MODEL(nrho,3), &
1164 !
1165  transport%DIFF_NI(nrho,nion,3), &
1166  transport%VCONV_NI(nrho,nion,3), &
1167 ! TRANSPORT%DIFF_NI(NRHO,NION), &
1168 ! TRANSPORT%VCONV_NI(NRHO,NION), &
1169  transport%DIFF_NI_MODEL(nrho,nion,3), &
1170  transport%VCONV_NI_MODEL(nrho,nion,3), &
1171 !
1172  transport%C1(3), &
1173  transport%DIFF_TI(nrho,nion), &
1174  transport%VCONV_TI(nrho,nion), &
1175  transport%QGI(nrho,nion), &
1176 !
1177  transport%DIFF_TE(nrho), &
1178  transport%VCONV_TE(nrho), &
1179  transport%QGE(nrho), &
1180 !
1181  transport%DIFF_VTOR(nrho,nion), &
1182  transport%VCONV_VTOR(nrho,nion), &
1183 !
1184  stat=istat)
1185 
1186 ! +++ Error checking and reporting
1187  IF (istat /= 0) THEN
1188  ifail = max(ifail,1) ! Failure to allocate
1189  write(*,*) 'ALLOCATE_TRANSPORT_COEFFICIENTS: Failure to allocate'
1190  RETURN
1191  ELSE
1192  ifail = max(ifail,0) ! Normal return
1193  END IF
1194 
1195 ! +++ Set dimensions
1196  transport%NRHO = nrho
1197  transport%NION = nion
1198 
1199  transport%SIGMA_SOURCE = 1
1200 
1201 ! Zero out arrays
1202 
1203  transport%SIGMA(:) = 0.0_r8
1204 
1205  transport%DIFF_NE(:,:) = 0.0_r8
1206  transport%VCONV_NE(:,:) = 0.0_r8
1207 ! TRANSPORT%DIFF_NE(:) = 0.0_R8
1208 ! TRANSPORT%VCONV_NE(:) = 0.0_R8
1209  transport%DIFF_NE_MODEL(:,:) = 0.0_r8
1210  transport%VCONV_NE_MODEL(:,:) = 0.0_r8
1211 
1212  transport%DIFF_NI(:,:,:) = 0.0_r8
1213  transport%VCONV_NI(:,:,:) = 0.0_r8
1214 ! TRANSPORT%DIFF_NI(:,:) = 0.0_R8
1215 ! TRANSPORT%VCONV_NI(:,:) = 0.0_R8
1216  transport%DIFF_NI_MODEL(:,:,:) = 0.0_r8
1217  transport%VCONV_NI_MODEL(:,:,:) = 0.0_r8
1218 
1219  transport%C1(:) = 0.0_r8
1220  transport%DIFF_TI(:,:) = 0.0_r8
1221  transport%VCONV_TI(:,:) = 0.0_r8
1222  transport%QGI(:,:) = 0.0_r8
1223 
1224  transport%DIFF_TE(:) = 0.0_r8
1225  transport%VCONV_TE(:) = 0.0_r8
1226  transport%QGE(:) = 0.0_r8
1227 
1228  transport%DIFF_VTOR(:,:) = 0.0_r8
1229  transport%VCONV_VTOR(:,:) = 0.0_r8
1230 
1231 
1232  END SUBROUTINE allocate_transport_coefficients
1233 
1234 
1235 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1236 ! +++ Deallocate plasma profiles needed by the transport solver
1237 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1243 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1244  SUBROUTINE deallocate_transport_coefficients (TRANSPORT, ifail)
1245 
1246 ! +++ Input/Output:
1247  TYPE (transport_coefficients) :: transport
1248  INTEGER, INTENT (INOUT) :: ifail
1249 
1250 ! +++ Local variables:
1251  INTEGER :: istat
1252 
1253  DEALLOCATE (transport%SIGMA_SOURCE, &
1254  transport%SIGMA, &
1255 !
1256  transport%DIFF_NI, &
1257  transport%VCONV_NI, &
1258  transport%DIFF_NI_MODEL, &
1259  transport%VCONV_NI_MODEL, &
1260 !
1261  transport%DIFF_NE, &
1262  transport%VCONV_NE, &
1263  transport%DIFF_NE_MODEL, &
1264  transport%VCONV_NE_MODEL, &
1265 !
1266  transport%C1, &
1267  transport%DIFF_TI, &
1268  transport%VCONV_TI, &
1269  transport%QGI, &
1270  transport%QGE, &
1271 !
1272  transport%DIFF_TE, &
1273  transport%VCONV_TE, &
1274 !
1275  transport%DIFF_VTOR, &
1276  transport%VCONV_VTOR, &
1277 !
1278  stat=istat)
1279 
1280 
1281 ! +++ Error checking and reporting
1282  IF (istat /= 0) THEN
1283  ifail = max(ifail,1) ! Failure to allocate
1284  write(*,*) 'DEALLOCATE_TRANSPORT_COEFFICIENTS: Failure to deallocate'
1285  RETURN
1286  ELSE
1287  ifail = max(ifail,0) ! Normal return
1288  END IF
1289 
1290  END SUBROUTINE deallocate_transport_coefficients
1291 
1292 
1293 
1294 
1295 
1296 
1297 ! ----------------------- SOURCES & SINKS ---------------------- !
1298 
1299 
1300 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1301 ! +++ Allocate profiles of sources needed by the transport solver
1302 
1303 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1309 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1310  SUBROUTINE allocate_sources_and_sinks (NRHO, NION, SOURCES, ifail)
1311 
1312 ! +++ Input/Output:
1313  INTEGER, INTENT (IN) :: nrho, nion
1314  TYPE (sources_and_sinks) :: sources
1315  INTEGER, INTENT (INOUT) :: ifail
1316 
1317 ! Local variables
1318  INTEGER :: istat
1319 
1320  ALLOCATE (sources%SIGMA(nrho), &
1321 !
1322  sources%CURR_EXP(nrho), &
1323  sources%CURR_IMP(nrho), &
1324 !
1325  sources%SE_EXP(nrho), &
1326  sources%SE_IMP(nrho), &
1327 !
1328  sources%SI_EXP(nrho,nion), &
1329  sources%SI_IMP(nrho,nion), &
1330 !
1331  sources%QI_EXP(nrho,nion), &
1332  sources%QI_IMP(nrho,nion), &
1333 !
1334  sources%QOH(nrho), &
1335  sources%QE_EXP(nrho), &
1336  sources%QE_IMP(nrho), &
1337 !
1338  sources%UI_EXP(nrho,nion), &
1339  sources%UI_IMP(nrho,nion), &
1340 !
1341  stat=istat)
1342 
1343 
1344 ! +++ Error checking and reporting
1345  IF (istat /= 0) THEN
1346  ifail = max(ifail,1) ! Failure to allocate
1347  write(*,*) 'ALLOCATE_SOURCES_AND_SINKS: Failure to allocate'
1348  RETURN
1349  ELSE
1350  ifail = max(ifail,0) ! Normal return
1351  END IF
1352 
1353 ! +++ Set dimensions
1354  sources%NRHO = nrho
1355  sources%NION = nion
1356 
1357 ! +++ Zero out arrays
1358  sources%SIGMA(:) = 0.0_r8
1359 
1360  sources%CURR_EXP(:) = 0.0_r8
1361  sources%CURR_IMP(:) = 0.0_r8
1362 
1363  sources%SE_EXP(:) = 0.0_r8
1364  sources%SE_IMP(:) = 0.0_r8
1365 
1366  sources%SI_EXP(:,:) = 0.0_r8
1367  sources%SI_IMP(:,:) = 0.0_r8
1368 
1369  sources%QI_EXP(:,:) = 0.0_r8
1370  sources%QI_IMP(:,:) = 0.0_r8
1371 
1372  sources%QOH(:) = 0.0_r8
1373  sources%QE_EXP(:) = 0.0_r8
1374  sources%QE_IMP(:) = 0.0_r8
1375 
1376  sources%UI_EXP(:,:) = 0.0_r8
1377  sources%UI_IMP(:,:) = 0.0_r8
1378 
1379  END SUBROUTINE allocate_sources_and_sinks
1380 
1381 
1382 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1383 ! +++ Deallocate plasma profiles needed by the transport solver
1384 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1390 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1391  SUBROUTINE deallocate_sources_and_sinks (SOURCES, ifail)
1392 
1393 ! +++ Input/Output:
1394  TYPE (sources_and_sinks) :: sources
1395  INTEGER, INTENT (INOUT) :: ifail
1396 
1397 ! +++ Local variables:
1398  INTEGER :: istat
1399 
1400  DEALLOCATE (sources%SIGMA, &
1401 !
1402  sources%CURR_EXP, &
1403  sources%CURR_IMP, &
1404 !
1405  sources%SE_EXP, &
1406  sources%SE_IMP, &
1407 !
1408  sources%SI_EXP, &
1409  sources%SI_IMP, &
1410 !
1411  sources%QI_EXP, &
1412  sources%QI_IMP, &
1413 !
1414  sources%QOH, &
1415  sources%QE_EXP, &
1416  sources%QE_IMP, &
1417 !
1418  sources%UI_EXP, &
1419  sources%UI_IMP, &
1420 !
1421  stat=istat)
1422 
1423 
1424 ! +++ Error checking and reporting
1425  IF (istat /= 0) THEN
1426  ifail = max(ifail,1) ! Failure to allocate
1427  write(*,*) 'DEALLOCATE_SOURCES_AND_SINKS: Failure to deallocate'
1428  RETURN
1429  ELSE
1430  ifail = max(ifail,0) ! Normal return
1431  END IF
1432 
1433  END SUBROUTINE deallocate_sources_and_sinks
1434 
1435 
1436 
1437 
1438 
1439 
1440 
1441 
1442 
1443 ! ----------------------- COLLISIONS ---------------------- !
1444 
1445 
1446 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1447 ! +++ Allocate profiles of sources needed by the transport solver
1448 
1449 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1455 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1456  SUBROUTINE allocate_collisionality (NRHO, NION, COLLISIONS, ifail)
1457 
1458 ! +++ Input/Output:
1459  INTEGER, INTENT (IN) :: nrho, nion
1460  TYPE (collisionality) :: collisions
1461  INTEGER, INTENT (INOUT) :: ifail
1462 
1463 ! Local variables
1464  INTEGER :: istat
1465 
1466  ALLOCATE (collisions%SIGMA(nrho), &
1467  collisions%VZI(nrho,nion), &
1468  collisions%QZI(nrho,nion), &
1469  collisions%VEI(nrho,nion), &
1470  collisions%QEI(nrho,nion), &
1471  collisions%WZI(nrho,nion), &
1472  collisions%UZI(nrho,nion), &
1473  collisions%VIE(nrho), &
1474  collisions%QIE(nrho), &
1475  collisions%VII(nrho,nion,nion), &
1476  collisions%WII(nrho,nion,nion), &
1477 !
1478  stat=istat)
1479 
1480 
1481 ! +++ Error checking and reporting
1482  IF (istat /= 0) THEN
1483  ifail = max(ifail,1) ! Failure to allocate
1484  write(*,*) 'ALLOCATE_COLLISIONALITY: Failure to allocate'
1485  RETURN
1486  ELSE
1487  ifail = max(ifail,0) ! Normal return
1488  END IF
1489 
1490 ! +++ Set dimensions
1491  collisions%NRHO = nrho
1492  collisions%NION = nion
1493 
1494 ! +++ Zero out arrays
1495  collisions%SIGMA(:) = 0.0_r8
1496  collisions%VZI(:,:) = 0.0_r8
1497  collisions%QZI(:,:) = 0.0_r8
1498  collisions%VEI(:,:) = 0.0_r8
1499  collisions%QEI(:,:) = 0.0_r8
1500  collisions%WZI(:,:) = 0.0_r8
1501  collisions%UZI(:,:) = 0.0_r8
1502  collisions%VIE(:) = 0.0_r8
1503  collisions%QIE(:) = 0.0_r8
1504  collisions%VII(:,:,:) = 0.0_r8
1505  collisions%WII(:,:,:) = 0.0_r8
1506 
1507  END SUBROUTINE allocate_collisionality
1508 
1509 
1510 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1511 ! +++ Deallocate plasma profiles needed by the transport solver
1512 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1518 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1519  SUBROUTINE deallocate_collisionality (COLLISIONS, ifail)
1520 
1521 ! +++ Input/Output:
1522  TYPE (collisionality) :: collisions
1523  INTEGER, INTENT (INOUT) :: ifail
1524 
1525 ! +++ Local variables:
1526  INTEGER :: istat
1527 
1528  DEALLOCATE (collisions%SIGMA, &
1529  collisions%VZI, &
1530  collisions%QZI, &
1531  collisions%VEI, &
1532  collisions%QEI, &
1533  collisions%WZI, &
1534  collisions%UZI, &
1535  collisions%VIE, &
1536  collisions%QIE, &
1537  collisions%VII, &
1538  collisions%WII, &
1539 !
1540  stat=istat)
1541 
1542 
1543 ! +++ Error checking and reporting
1544  IF (istat /= 0) THEN
1545  ifail = max(ifail,1) ! Failure to allocate
1546  write(*,*) 'DEALLOCATE_COLLISIONALITY: Failure to deallocate'
1547  RETURN
1548  ELSE
1549  ifail = max(ifail,0) ! Normal return
1550  END IF
1551 
1552  END SUBROUTINE deallocate_collisionality
1553 
1554 
1555 
1556 ! ----------------------- IMPURITY PROFILES ---------------------- !
1557 
1558 
1559 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1560 ! +++ Allocate plasma profiles needed by the transport solver
1561 
1562 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1568 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1569  SUBROUTINE allocate_impurity_profiles (NRHO, NIMP, NZIMP, IMPURITY, ifail)
1570 
1571 ! +++ Input/Output:
1572  INTEGER, INTENT (IN) :: nrho, nimp, nzimp
1573  TYPE (impurity_profiles) :: impurity
1574  INTEGER, INTENT (INOUT) :: ifail
1575 
1576 ! +++ Local variables:
1577  INTEGER :: istat
1578 
1579  ALLOCATE (impurity%NZ(nrho,nimp,nzimp), &
1580  impurity%FLUX_NZ(nrho,nimp,nzimp), &
1581  impurity%ZIMP(nrho,nimp,nzimp), &
1582  impurity%ZIMP2(nrho,nimp,nzimp), &
1583  stat=istat)
1584 
1585 ! +++ Error checking and reporting
1586  IF (istat /= 0) THEN
1587  ifail = max(ifail,1) ! Failure to allocate
1588  write(*,*) 'ALLOCATE_IMPURITY_PROFILES: Failure to allocate'
1589  RETURN
1590  ELSE
1591  ifail = max(ifail,0) ! Normal return
1592  END IF
1593 
1594 ! +++ Set dimensions
1595  impurity%NRHO = nrho
1596  impurity%NIMP = nimp
1597  impurity%NZIMP = nzimp
1598 
1599 ! Zero out arrays
1600 
1601  impurity%NZ(:,:,:) = 0.0_r8
1602  impurity%FLUX_NZ(:,:,:) = 0.0_r8
1603  impurity%ZIMP(:,:,:) = 0.0_r8
1604  impurity%ZIMP2(:,:,:) = 0.0_r8
1605 
1606 
1607  END SUBROUTINE allocate_impurity_profiles
1608 
1609 
1610 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1611 ! +++ Deallocate plasma profiles needed by the transport solver
1612 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1618 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1619  SUBROUTINE deallocate_impurity_profiles (IMPURITY, ifail)
1620 
1621 ! +++ Input/Output:
1622  TYPE (impurity_profiles) :: impurity
1623  INTEGER, INTENT (INOUT) :: ifail
1624 
1625 ! +++ Local variables:
1626  INTEGER :: istat
1627 
1628  DEALLOCATE (impurity%NZ, &
1629  impurity%FLUX_NZ, &
1630  impurity%ZIMP, &
1631  impurity%ZIMP2, &
1632  stat=istat)
1633 
1634 
1635 ! +++ Error checking and reporting
1636  IF (istat /= 0) THEN
1637  ifail = max(ifail,1) ! Failure to allocate
1638  write(*,*) 'DEALLOCATE_IMPURITY_PROFILES: Failure to deallocate'
1639  RETURN
1640  ELSE
1641  ifail = max(ifail,0) ! Normal return
1642  END IF
1643 
1644  END SUBROUTINE deallocate_impurity_profiles
1645 
1646 
1647 
1648 
1649 ! ---------------- PARAMETERS FOR TIME EVOLUTION --------------- !
1650 
1651 
1652 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1653 ! +++ Allocate parameters required by time evolution
1654 
1655 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1661 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1662  SUBROUTINE allocate_time_evolution (NRHO, NION, EVOLUTION, ifail)
1663 
1664 ! +++ Input/Output:
1665  INTEGER, INTENT (IN) :: nrho, nion
1666  TYPE (time_evolution) :: evolution
1667  INTEGER, INTENT (INOUT) :: ifail
1668 
1669 ! +++ Local variables:
1670  INTEGER :: istat
1671 
1672 
1673 
1674  ALLOCATE (evolution%PSIM(nrho), &
1675  evolution%DPSIM(nrho), &
1676  evolution%NIM(nrho,nion), &
1677  evolution%DNIM(nrho,nion), &
1678  evolution%TIM(nrho,nion), &
1679  evolution%DTIM(nrho,nion), &
1680  evolution%NEM(nrho), &
1681  evolution%DNEM(nrho), &
1682  evolution%TEM(nrho), &
1683  evolution%DTEM(nrho), &
1684  evolution%VTORM(nrho,nion), &
1685  evolution%DVTORM(nrho,nion), &
1686  evolution%VPRM(nrho), &
1687  evolution%G2M(nrho), &
1688  evolution%BTM, &
1689  stat=istat)
1690 
1691 ! +++ Error checking and reporting:
1692  IF (istat /= 0) THEN
1693  ifail = max(ifail,1) ! Failure to allocate
1694  write(*,*) 'ALLOCATE_TIME_EVOLUTION: Failure to allocate'
1695  RETURN
1696  ELSE
1697  ifail = max(ifail,0) ! Normal return
1698  END IF
1699 
1700 ! +++ Set control parameters:
1701  evolution%PSIM(:) = 0.0_r8
1702  evolution%DPSIM(:) = 0.0_r8
1703  evolution%NIM(:,:) = 0.0_r8
1704  evolution%DNIM(:,:) = 0.0_r8
1705  evolution%TIM(:,:) = 0.0_r8
1706  evolution%DTIM(:,:) = 0.0_r8
1707  evolution%NEM(:) = 0.0_r8
1708  evolution%DNEM(:) = 0.0_r8
1709  evolution%TEM(:) = 0.0_r8
1710  evolution%DTEM(:) = 0.0_r8
1711  evolution%VTORM(:,:) = 0.0_r8
1712  evolution%DVTORM(:,:) = 0.0_r8
1713  evolution%VPRM(:) = 0.0_r8
1714  evolution%G2M(:) = 0.0_r8
1715  evolution%BTM = 0.0_r8
1716 
1717  END SUBROUTINE allocate_time_evolution
1718 
1719 
1720 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1721 ! +++ Deallocate plasma profiles needed by the transport solver
1722 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1728 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1729  SUBROUTINE deallocate_time_evolution (EVOLUTION, ifail)
1730 
1731 ! +++ Input/Output:
1732  TYPE (time_evolution) :: evolution
1733  INTEGER, INTENT (INOUT) :: ifail
1734 
1735 ! +++ Local variables:
1736  INTEGER :: istat
1737 
1738  DEALLOCATE (evolution%PSIM, &
1739  evolution%DPSIM, &
1740  evolution%NIM, &
1741  evolution%DNIM, &
1742  evolution%TIM, &
1743  evolution%DTIM, &
1744  evolution%NEM, &
1745  evolution%DNEM, &
1746  evolution%TEM, &
1747  evolution%DTEM, &
1748  evolution%VTORM, &
1749  evolution%DVTORM, &
1750  evolution%VPRM, &
1751  evolution%G2M, &
1752  evolution%BTM, &
1753  stat=istat)
1754 
1755 
1756 ! +++ Error checking and reporting
1757  IF (istat /= 0) THEN
1758  ifail = max(ifail,1) ! Failure to allocate
1759  write(*,*) 'DEALLOCATE_TIME_EVOLUTION: Failure to deallocate'
1760  RETURN
1761  ELSE
1762  ifail = max(ifail,0) ! Normal return
1763  END IF
1764 
1765  END SUBROUTINE deallocate_time_evolution
1766 
1767 
1768 
1769 
1770 ! ---------------- RUN_CONTROL --------------- !
1771 
1772 
1773 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1774 ! +++ Allocate parameters required by the run control and
1775 ! iterations loop
1776 
1777 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1783 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1784  SUBROUTINE allocate_run_control (CONTROL, ifail)
1785 
1786 ! +++ Input/Output:
1787  TYPE (run_control) :: control
1788  INTEGER, INTENT (INOUT) :: ifail
1789 
1790 ! +++ Local variables:
1791  INTEGER :: istat
1792 
1793  ALLOCATE (control%TAU, &
1794  control%AMIX, &
1795  control%AMIXTR, &
1796  control%CONV, &
1797  control%CONVREC, &
1798  stat=istat)
1799 
1800 ! +++ Error checking and reporting:
1801  IF (istat /= 0) THEN
1802  ifail = max(ifail,1) ! Failure to allocate
1803  write(*,*) 'ALLOCATE_RUN_CONTROL: Failure to allocate'
1804  RETURN
1805  ELSE
1806  ifail = max(ifail,0) ! Normal return
1807  END IF
1808 
1809 ! +++ Set control parameters:
1810  control%SOLVER_TYPE = 0
1811  control%SIGMA_SOURCE = 1 ! default to taking plasma electrical conductivity from the transport module
1812  control%QUASI_NEUT = 0 ! default: electrons fron quasi-neutrality
1813  control%TAU = 0.0_r8
1814  control%AMIX = 1.0_r8
1815  control%AMIXTR = 1.0_r8
1816  control%CONV = 1.0_r8
1817  control%CONVREC = 0.0_r8
1818 
1819  END SUBROUTINE allocate_run_control
1820 
1821 
1822 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1823 ! +++ Deallocate plasma profiles needed by the transport solver
1824 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1830 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1831  SUBROUTINE deallocate_run_control (CONTROL, ifail)
1832 
1833 ! +++ Input/Output:
1834  TYPE (run_control) :: control
1835  INTEGER, INTENT (INOUT) :: ifail
1836 
1837 ! +++ Local variables:
1838  INTEGER :: istat
1839 
1840  DEALLOCATE (control%TAU, &
1841  control%AMIX, &
1842  control%AMIXTR, &
1843  control%CONV, &
1844  control%CONVREC, &
1845  stat=istat)
1846 
1847 
1848 ! +++ Error checking and reporting
1849  IF (istat /= 0) THEN
1850  ifail = max(ifail,1) ! Failure to allocate
1851  write(*,*) 'DEALLOCATE_RUN_CONTROL: Failure to deallocate'
1852  RETURN
1853  ELSE
1854  ifail = max(ifail,0) ! Normal return
1855  END IF
1856 
1857  END SUBROUTINE deallocate_run_control
1858 
1859 
1860 
1861 
1862 
1863 
1864 
1865 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1866 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1867 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
1868 
1869 END MODULE ets_plasma
1870 
1871 
1872 
1873 
1874 
1875 
1876 
subroutine allocate_magnetic_geometry(NRHO, GEOMETRY, ifail)
Definition: ets_plasma.f90:502
IMPURITY.
Definition: impurity.F90:8
subroutine profiles(p0, rbphi, dp0, drbphi, a)
Definition: profiles.f90:1
subroutine allocate_global_param(GLOBAL, ifail)
Definition: ets_plasma.f90:630
subroutine allocate_plasma_profiles(NRHO, NION, PROFILES, ifail)
Definition: ets_plasma.f90:717
subroutine allocate_sources_and_sinks(NRHO, NION, SOURCES, ifail)
Allocate profiles of sources needed by the transport solver.
subroutine allocate_run_control(CONTROL, ifail)
Allocate parameters required by the run control and iterations loop.
subroutine allocate_impurity_profiles(NRHO, NIMP, NZIMP, IMPURITY, ifail)
Allocate plasma profiles needed by the transport solver.
subroutine deallocate_run_control(CONTROL, ifail)
Deallocate plasma profiles needed by the transport solver.
subroutine allocate_transport_coefficients(NRHO, NION, TRANSPORT, ifail)
Allocate profiles of transport coefficients needed by the transport solver.
subroutine deallocate_magnetic_geometry(GEOMETRY, ifail)
Definition: ets_plasma.f90:575
subroutine deallocate_transport_coefficients(TRANSPORT, ifail)
Deallocate plasma profiles needed by the transport solver.
subroutine deallocate_sources_and_sinks(SOURCES, ifail)
Deallocate plasma profiles needed by the transport solver.
subroutine deallocate_collisionality(COLLISIONS, ifail)
Deallocate plasma profiles needed by the transport solver.
subroutine deallocate_time_evolution(EVOLUTION, ifail)
Deallocate plasma profiles needed by the transport solver.
subroutine allocate_collisionality(NRHO, NION, COLLISIONS, ifail)
Allocate profiles of sources needed by the transport solver???
The module declares types of variables used in ETS (transport code)
Definition: ets_plasma.f90:8
subroutine deallocate_impurity_profiles(IMPURITY, ifail)
Deallocate plasma profiles needed by the transport solver.
subroutine evolution(T, R_in, R_out, El, Tr_l, Tr_U, Ip)
subroutine deallocate_plasma_profiles(PROFILES, ifail)
Deallocate plasma profiles needed by the transport solver.
Definition: ets_plasma.f90:992
subroutine allocate_time_evolution(NRHO, NION, EVOLUTION, ifail)
Allocate parameters required by time evolution.
subroutine deallocate_global_param(GLOBAL, ifail)
Definition: ets_plasma.f90:677