ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
fc2k_ETB_transport.f90
Go to the documentation of this file.
1 !-------------------------------------------------------!
2 !-------------------------------------------------------!
3 
4  SUBROUTINE etb_transport (CORETRANSP_IN, CORETRANSP_OUT,&
5  diff_ni, vconv_ni, &
6  diff_ne, vconv_ne, &
7  diff_ti, vconv_ti, &
8  diff_te, vconv_te, &
9  diff_vtor, vconv_vtor, &
10  diff_nz, vconv_nz, &
11  diff_tz, vconv_tz, &
12  rho_etb)
13 
14 !-------------------------------------------------------!
15 ! This routine is used by the ETS workflow !
16 ! to reduce transport inside ETB !
17 !-------------------------------------------------------!
18 ! Source: --- !
19 ! Developers: D.Kalupin !
20 ! Kontacts: Denis.Kalupin@efda.org !
21 ! !
22 ! Comments: output CORETRANSP CPO is !
23 ! allocated inside the module !
24 ! !
25 !-------------------------------------------------------!
26 
27  USE euitm_schemas
28  USE euitm_routines
29  USE copy_structures
30  USE itm_types
32 
33 
34  IMPLICIT NONE
35 
36  INTEGER :: ifail
37 
38  TYPE (type_coretransp), POINTER :: coretransp_in(:) !input CPO with transport
39  TYPE (type_coretransp), POINTER :: coretransp_out(:) !output CPO with transport
40 
41 
42 ! +++ Dimensions:
43  INTEGER, PARAMETER :: nslice = 1 !number of CPO ocurancies in the work flow
44  INTEGER :: nrho, irho !number of radial points (input, determined from COREPROF CPO)
45  INTEGER :: nnucl !number of nuclei species
46  INTEGER :: nion, iion !number of ion species
47  INTEGER :: nimp, iimp !number of impurity species
48  INTEGER, ALLOCATABLE :: nzimp(:) !number of ionization states for each impurity
49  INTEGER :: izimp
50  INTEGER :: nneut, ineut !number of neutrals species
51  INTEGER, ALLOCATABLE :: ncomp(:) !number of components for each neutral
52  INTEGER, ALLOCATABLE :: ntype(:) !number of types for each neutral
53 
54 
55  REAL(R8) :: rho_etb
56  REAL(R8) :: diff_ni(30), vconv_ni(30)
57  REAL(R8) :: diff_ti(30), vconv_ti(30)
58  REAL(R8) :: diff_ne, vconv_ne
59  REAL(R8) :: diff_te, vconv_te
60  REAL(R8) :: diff_vtor(30), vconv_vtor(30)
61  REAL(R8) :: diff_nz(100), vconv_nz(100)
62  REAL(R8) :: diff_tz(100), vconv_tz(100)
63 
64 ! +++ Set dimensions:
65  nrho = SIZE (coretransp_in(1)%VALUES(1)%rho_tor, dim=1)
66  CALL get_comp_dimensions(coretransp_in(1)%COMPOSITIONS, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp)
67 
68 
69 
70 ! +++ Allocate output CPO:
71  ALLOCATE (coretransp_out(1))
72  CALL copy_cpo(coretransp_in(1), coretransp_out(1))
73 
74 
75 ! +++ Save output in CPO:
76  DO irho = 1, nrho
77 
78  IF (coretransp_out(1)%VALUES(1)%rho_tor(irho)/coretransp_out(1)%VALUES(1)%rho_tor(nrho) .GT. rho_etb) THEN
79 
80  coretransp_out(1)%VALUES(1)%te_transp%diff_eff(irho) = diff_te
81  coretransp_out(1)%VALUES(1)%te_transp%vconv_eff(irho) = vconv_te
82  coretransp_out(1)%VALUES(1)%ne_transp%diff_eff(irho,1) = diff_ne
83  coretransp_out(1)%VALUES(1)%ne_transp%vconv_eff(irho,1) = vconv_ne
84  coretransp_out(1)%VALUES(1)%ne_transp%diff_eff(irho,2) = 0.0_r8
85  coretransp_out(1)%VALUES(1)%ne_transp%vconv_eff(irho,2) = 0.0_r8
86  coretransp_out(1)%VALUES(1)%ne_transp%diff_eff(irho,3) = 0.0_r8
87  coretransp_out(1)%VALUES(1)%ne_transp%vconv_eff(irho,3) = 0.0_r8
88 
89  DO iion = 1, nion
90  coretransp_out(1)%VALUES(1)%ni_transp%diff_eff(irho,iion,1) = diff_ni(iion)
91  coretransp_out(1)%VALUES(1)%ni_transp%vconv_eff(irho,iion,1) = vconv_ni(iion)
92  coretransp_out(1)%VALUES(1)%ni_transp%diff_eff(irho,iion,2) = 0.0_r8
93  coretransp_out(1)%VALUES(1)%ni_transp%vconv_eff(irho,iion,2) = 0.0_r8
94  coretransp_out(1)%VALUES(1)%ni_transp%diff_eff(irho,iion,3) = 0.0_r8
95  coretransp_out(1)%VALUES(1)%ni_transp%vconv_eff(irho,iion,3) = 0.0_r8
96  coretransp_out(1)%VALUES(1)%ti_transp%diff_eff(irho,iion) = diff_ti(iion)
97  coretransp_out(1)%VALUES(1)%ti_transp%vconv_eff(irho,iion) = vconv_ti(iion)
98  coretransp_out(1)%VALUES(1)%vtor_transp%diff_eff(irho,iion) = diff_vtor(iion)
99  coretransp_out(1)%VALUES(1)%vtor_transp%vconv_eff(irho,iion) = vconv_vtor(iion)
100  END DO
101 
102  IF (nimp > 0) THEN
103  DO iimp = 1, nimp
104  DO izimp = 1, nzimp(iimp)
105  coretransp_out(1)%VALUES(1)%nz_transp(iimp)%diff_eff(irho,izimp) = diff_nz(iimp)
106  coretransp_out(1)%VALUES(1)%nz_transp(iimp)%vconv_eff(irho,izimp)= vconv_nz(iimp)
107  coretransp_out(1)%VALUES(1)%tz_transp(iimp)%diff_eff(irho,izimp) = diff_tz(iimp)
108  coretransp_out(1)%VALUES(1)%tz_transp(iimp)%vconv_eff(irho,izimp)= vconv_tz(iimp)
109  END DO
110  END DO
111  ENDIF
112 
113  END IF
114 
115  END DO
116 
117 
118 
119  RETURN
120 
121  END SUBROUTINE etb_transport
122 !-------------------------------------------------------!
123 !-------------------------------------------------------!
subroutine get_comp_dimensions(COMPOSITIONS, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP)
This module contains routines for allocation/deallocation if CPOs used in ETS.
subroutine etb_transport(CORETRANSP_IN, CORETRANSP_OUT, DIFF_NI, VCONV_NI, DIFF_NE, VCONV_NE, DIFF_TI, VCONV_TI, DIFF_TE, VCONV_TE, DIFF_VTOR, VCONV_VTOR, DIFF_NZ, VCONV_NZ, DIFF_TZ, VCONV_TZ, RHO_ETB)