ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
gbtransport.f90
Go to the documentation of this file.
1 MODULE gbtransport
2 
3 CONTAINS
4 
5 
6 
7 
8 
9 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
10 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
11 SUBROUTINE gb_transport(EQUILIBRIUM, COREPROF, CORETRANSP)
12 
13 !-------------------------------------------------------!
14 ! This routine checks for the consistency of !
15 ! profiles (psi, q, jparallel) and equilibrium !
16 ! !
17 ! information received in: EQUILIBRIUM !
18 ! COREPROF !
19 ! !
20 ! information saved in: CORETRANSP !
21 ! (allocated internaly) !
22 ! !
23 ! controling parameter: CODE_PARAMETERS !
24 ! !
25 !-------------------------------------------------------!
26 ! Source: --- !
27 ! Developers: D.Kalupin !
28 ! Kontacts: Denis.Kalupin@efda.org !
29 ! !
30 ! Comments: created for V&V between ETS, JETTO !
31 ! and ASTRA !
32 ! !
33 !-------------------------------------------------------!
34 
35 
36  USE euitm_schemas
37  USE euitm_routines
38  USE itm_constants
39 
40  USE copy_structures
41  USE deallocate_structures
42 
44 
45  IMPLICIT NONE
46 
47 
48 ! +++ CPO derived types:
49  TYPE (type_equilibrium), POINTER :: equilibrium(:) !input CPO with geometry quantities from previous time
50  TYPE (type_coreprof), POINTER :: coreprof(:) !input CPO with plasma profiles
51  TYPE (type_coretransp), POINTER :: coretransp(:) !output CPO with transport coefficients
52 
53 
54 ! +++ Local parameters:
55  REAL(R8) :: time
56  REAL(R8), ALLOCATABLE :: amj(:)
57  REAL(R8), ALLOCATABLE :: zmj(:)
58  REAL(R8), ALLOCATABLE :: rho(:)
59  REAL(R8), ALLOCATABLE :: te(:)
60  REAL(R8), ALLOCATABLE :: ne(:)
61  REAL(R8), ALLOCATABLE :: mu(:)
62  REAL(R8) :: roc
63  REAL(R8) :: hro
64  REAL(R8) :: btor
65  REAL(R8) :: ylp, yhagb, hagb, yhatl, hatl
66 
67  REAL(R8), ALLOCATABLE :: diff_te(:) !Output: electron heat diffusion [m^2/s]
68  REAL(R8), ALLOCATABLE :: diff_ti(:,:) !Output: ion heat diffusion [m^2/s]
69 
70 
71 ! +++ Dimensions:
72  INTEGER, PARAMETER :: nocur = 1 !number of CPO ocurancies in the work flow
73  INTEGER :: nrho, irho !number of radial points (input, determined from COREPROF CPO)
74  INTEGER :: neq !number of radial points (input, determined from EQUILIBRIUM CPO)
75  INTEGER :: nnucl, inucl !number of nuclei species
76  INTEGER :: nion, iion !number of ion species
77  INTEGER :: nimp, iimp !number of impurity species
78  INTEGER, ALLOCATABLE :: nzimp(:) !number of ionization states for each impurity
79  INTEGER :: nneut, ineut !number of neutrals species
80  INTEGER, ALLOCATABLE :: ncomp(:) !number of components for each neutral
81  INTEGER, ALLOCATABLE :: ntype(:) !number of types for each neutral
82 
83 
84 
85 
86 ! +++ Set dimensions:
87  nrho = SIZE (coreprof(1)%rho_tor, dim=1)
88  CALL get_comp_dimensions(coreprof(1)%COMPOSITIONS, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp)
89 
90 
91 
92 ! +++ Allocate output CPO:
93  CALL allocate_coretransp_cpo(nocur, nrho, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, coretransp)
94  call deallocate_cpo(coretransp(1)%compositions)
95  CALL copy_cpo(coreprof(1)%compositions, coretransp(1)%compositions)
96 
97 
98 ! +++ Allocate local variables:
99  ALLOCATE ( amj(nion) )
100  ALLOCATE ( zmj(nion) )
101 
102  ALLOCATE ( rho(nrho) )
103  ALLOCATE ( te(nrho) )
104  ALLOCATE ( ne(nrho) )
105  ALLOCATE ( mu(nrho) )
106 
107  ALLOCATE ( diff_te(nrho) )
108  ALLOCATE ( diff_ti(nrho,nion) )
109 
110 
111 
112 ! +++ Local parameters:
113  time = coreprof(1)%time
114 
115  btor = coreprof(1)%toroid_field%b0
116 
117  rho = coreprof(1)%rho_tor
118 
119  te = coreprof(1)%te%value / 1.e3_r8 ! Temperature is specified in [keV]
120  ne = coreprof(1)%ne%value / 1.e19_r8 ! Density is specified in [10^19 m^-3]
121 
122  mu = 1.0_r8 / coreprof(1)%profiles1d%q%value
123 
124  roc = rho(nrho)
125 
126 
127 
128  DO iion = 1, nion
129 
130  inucl = coreprof(1)%COMPOSITIONS%IONS(iion)%nucindex
131 
132  amj(iion) = coreprof(1)%COMPOSITIONS%NUCLEI(inucl)%amn
133  zmj(iion) = coreprof(1)%COMPOSITIONS%IONS(iion)%zion
134 
135 
136  DO irho = 1, nrho
137 
138  !-------------------------------------------------------!
139  ! HAGB [m#2/s]: !
140  ! Heat conductivity Anomalous gyroBohm !
141  ! BOHM=c*Te/(e*B)=TE/BTOR*10^3[m^2/s] !
142  ! HAGB=BOHM*(dTe/dr)*a/Te*ro/a; ro=rl_i/omega_ci !
143  ! !
144  ! Source: M.Erba et al. JET-P(96)10 !
145  ! I.Vojtsekhovich 01-08-96 !
146  ! !
147  ! Usage: HE=...+0.035*HAGB*XSTEP(0.8); !
148  ! Modified by G.Pereverzev 14-JAN-97 !
149  ! to include recommended numerical !
150  ! pre-factor 0.035 !
151  ! !
152  !-------------------------------------------------------!
153 
154  IF ( irho.EQ.1 ) THEN
155  ylp = 0.0_r8
156  yhagb = 0.32_r8 * sqrt(amj(iion)) / btor**2 / zmj(iion)
157  ELSE
158  ylp = yhagb / (rho(irho)-rho(irho-1)) * &
159  abs(te(irho)-te(irho-1)) / (te(irho)+te(irho-1))
160  END IF
161  hagb = ylp*te(irho) * sqrt(te(irho))
162 
163 
164 
165  !-------------------------------------------------------!
166  ! HATL [m#2/s]: !
167  ! Heat conductivity Anomalous by Taroni for L-mode!
168  ! BOHM=c*Te/(e*B)=TE/BTOR*10^3[m^2/s] !
169  ! HATL=A_e*BOHM*q^2*(dp/dr)*a/p; !
170  ! A_e recommended = 2.5E-4 is included in YHATL !
171  ! Source: M.Erba et al. JET-R(95)02 !
172  ! (Pereverzev 04-AUG-95) !
173  ! According to M.Erba et al. JET-P(96)10 !
174  ! a*(dp/dr)/p is replaced with a*(dp_e/dr)/p_e !
175  ! (Pereverzev 14-JAN-97) !
176  ! !
177  !-------------------------------------------------------!
178  IF( irho.EQ.1 ) THEN
179  ylp = 0.0_r8
180  yhatl = 0.5_r8 * roc / btor
181  ELSE
182  ylp = yhatl / (rho(irho)-rho(irho-1)) * &
183  abs(ne(irho)*te(irho)-ne(irho-1)*te(irho-1)) / (ne(irho)+ne(irho-1))
184  END IF
185  hatl = ylp / mu(irho)**2
186 
187 
188  !-------------------------------------------------------!
189  ! Transport coefficients: !
190  ! XE = HATL+HAGB+... !
191  ! XI = 2*HATL+HAGB+... !
192  ! !
193  !-------------------------------------------------------!
194  diff_te(irho) = hatl + hagb
195  diff_ti(irho,iion) = 2.0_r8 * hatl + hagb
196 
197  END DO
198  END DO
199 
200 
201 ! +++ Save output in CPO:
202 !
203 ! Only electron and ion heat diffusion is updated
204 
205  coretransp(1)%time = time !time [s]
206 
207  coretransp(1)%VALUES(1)%rho_tor = rho !rho [m]
208 
209  coretransp(1)%VALUES(1)%sigma = 0.e0_r8
210 
211  coretransp(1)%VALUES(1)%te_transp%diff_eff = diff_te
212  coretransp(1)%VALUES(1)%te_transp%vconv_eff = 0.e0_r8
213 
214  coretransp(1)%VALUES(1)%ni_transp%diff_eff = 0.e0_r8
215  coretransp(1)%VALUES(1)%ni_transp%vconv_eff = 0.e0_r8
216 
217  coretransp(1)%VALUES(1)%ti_transp%diff_eff = diff_ti
218  coretransp(1)%VALUES(1)%ti_transp%vconv_eff = 0.e0_r8
219 
220  coretransp(1)%VALUES(1)%vtor_transp%diff_eff = 0.e0_r8
221  coretransp(1)%VALUES(1)%vtor_transp%vconv_eff = 0.e0_r8
222 
223 
224 
225 ! +++ Deallocate local variables:
226  DEALLOCATE ( amj )
227  DEALLOCATE ( zmj )
228 
229  DEALLOCATE ( rho )
230  DEALLOCATE ( te )
231  DEALLOCATE ( ne )
232  DEALLOCATE ( mu )
233 
234  DEALLOCATE ( diff_te )
235  DEALLOCATE ( diff_ti )
236 
237  DEALLOCATE ( nzimp )
238  if (allocated(ncomp)) DEALLOCATE ( ncomp )
239  if (allocated(ntype)) DEALLOCATE ( ntype )
240 
241 
242 END SUBROUTINE gb_transport
243 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
244 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
245 
246 
247 
248 END MODULE gbtransport
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 gb_transport(EQUILIBRIUM, COREPROF, CORETRANSP)
Definition: gbtransport.f90:11
subroutine allocate_coretransp_cpo(NSLICE, NRHO, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP, CORETRANSP)
This routine allocates CORETRANSP CPO.