ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
plasma_collisionality.f90
Go to the documentation of this file.
1 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
9 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
11 
12 CONTAINS
13 
14 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
15 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
16 
17 SUBROUTINE plasma_collisions &
18  (geometry,profiles,collisions,ifail)
19 
20 !-------------------------------------------------------!
21 ! This routine calculates the collision frquencies !
22 ! and various exchange terms determined by collisions!
23 !-------------------------------------------------------!
24 ! Source: --- !
25 ! Developers: S.Moradi, D.Kalupin !
26 ! Contacts: smoradi@ulb.ac.be !
27 ! D.Kalupin@fz-juelich.de !
28 !-------------------------------------------------------!
29 
30 ! +++ Declaration of variables:
31 
32  USE itm_constants
33  USE ets_plasma
34 
35  IMPLICIT NONE
36 
37 
38 ! +++ External parameters, input from / output to the work flow:
39  TYPE (magnetic_geometry) :: geometry !contains all geometry quantities
40  TYPE (plasma_profiles) :: profiles !contains profiles of plasma parameters
41  TYPE (collisionality) :: collisions !contains all terms determined by plasma collisions
42 
43  INTEGER :: ifail
44 
45 
46 
47 ! +++ Internal parameters:
48 ! Indexes and dimensions
49  INTEGER :: nrho !number of radial points (input)
50  INTEGER :: nion !number of ion species (input)
51 
52  INTEGER :: irho !current radial knot
53  INTEGER :: iion !ion index 1
54  INTEGER :: iz !ion imdex 2
55 
56 ! Plasma parameter profiles
57  REAL (R8) :: bt !toroidal magnetic field, [T]
58  REAL (R8) :: g2(geometry%nrho)
59 
60  REAL (R8) :: aion(profiles%nion) !ion mass number [--]
61  REAL (R8) :: zion(profiles%nion) !ion charge numbers [--]
62 
63  REAL (R8) :: ni(profiles%nrho,profiles%nion) !density of background ions, [m^-3]
64  REAL (R8) :: ti(profiles%nrho,profiles%nion) !ion temperature, [eV]
65  REAL (R8) :: ne(profiles%nrho) !electron density, [m^-3]
66  REAL (R8) :: te(profiles%nrho) !electron temperature, [eV]
67  REAL (R8) :: tzi, mzi, nzi !effective: ion temperature [eV], mass [g], and density [m^-3]
68  REAL (R8) :: vtor(profiles%nrho,profiles%nion) !ion toroidal velocity, [m/s]
69 
70 
71  INTEGER :: te_bnd_type !boundary condition type for electron temperature, if = 0, no energy exchange to electrons
72  INTEGER :: ti_bnd_type(profiles%nion) !boundary condition type for ion temperature, if = 0, no energy exchange to this ion component
73  INTEGER :: vtor_bnd_type(profiles%nion) !boundary condition type for ion rotation, if = 0, no momentum exchange to this ion component
74 
75 
76 ! Collision time and other intermediate quantities
77  REAL (R8) :: clog !Coulomb logarithm
78  REAL (R8) :: tau_e(profiles%nrho) !electron collision time, [s]
79  REAL (R8) :: tau_ei(profiles%nrho,profiles%nion) !electron-ion collision time, [s]
80  REAL (R8) :: tau_zi(profiles%nrho,profiles%nion) !ion-ion collision time, [s]
81 
82 
83 
84 ! +++ Output collision quantities:
85 ! current transport
86  REAL (R8) :: sigma(profiles%nrho) !plasma parallel conductivity, [(Ohm*m)^-1]
87 
88 ! electron energy transport
89  REAL (R8) :: vie(profiles%nrho) !energy sink from electrons to all ion components (frequency), [1/(m^3*s)]
90  REAL (R8) :: qie(profiles%nrho) !energy input to electrons from all ion components, [eV/(m^3*s)]
91 
92 ! ion energy transport
93  REAL (R8) :: vei(profiles%nrho,profiles%nion) !energy sink from ion component (IION) to electons (frequency), [1/(m^3*s)]
94  REAL (R8) :: vzi(profiles%nrho,profiles%nion) !energy sink from ion component (IION) to all other ions (frequency), [1/(m^3*s)]
95  REAL (R8) :: viz(profiles%nrho,profiles%nion,profiles%nion)!ion-ion collision frequency, MATRIX (NION,NION), [1/(m^3*s)]
96  REAL (R8) :: qzi(profiles%nrho,profiles%nion) !energy input to ion component (IION) from all other ions, [eV/(m^3*s)]
97  REAL (R8) :: qei(profiles%nrho,profiles%nion) !energy input to ion component (IION) from electons, [eV/(m^3*s)]
98 
99 ! ion momentum transport
100  REAL (R8) :: wiz(profiles%nrho,profiles%nion,profiles%nion)!ion-ion momentum exchange, MATRIX (NION,NION), [kg/(m^3*s)]
101  REAL (R8) :: wzi(profiles%nrho,profiles%nion) !momentum sink from ion component (IION) to all other ions (frequency), [kg/(m^2*s)]
102  REAL (R8) :: uzi(profiles%nrho,profiles%nion) !momentum input to ion component (IION) from all other ions, [kg/(m*s^2)]
103 
104 
105 ! +++ Constants:
106  REAL (R8), PARAMETER :: me = itm_me*1e3_r8 !electron mass [g]
107  REAL (R8), PARAMETER :: mp = itm_mp*1e3_r8 !proton mass [g]
108  REAL (R8), PARAMETER :: e = itm_qe*3e9_r8 !elementary charge, [esu]
109 
110  REAL (R8), PARAMETER :: ct = itm_ev*1e7_r8 !energy associated with 1 eV, [erg]
111  REAL (R8), PARAMETER :: cn = 1.e-6_r8 !density convergence from [m^-3] to [cm^-3]
112  REAL (R8), PARAMETER :: cs = 9.e9_r8 !conductivity convergence from [(Ohm*m)^-1] to [s^-1]
113  REAL (R8), PARAMETER :: cm = 1.e-3_r8 !mass convergence from [g] to [kg]
114 
115 
116 
117 
118 ! +++ Set up dimensions:
119  nrho = profiles%NRHO
120  nion = profiles%NION
121 
122 
123 
124 ! +++ Boundary conditions for electron temperature:
125  te_bnd_type = profiles%TE_BND_TYPE
126 
127 
128 ! +++ Boundary conditions for ion temperature and rotation:
129  ion_loop1: DO iion = 1,nion
130  ti_bnd_type(iion) = profiles%TI_BND_TYPE(iion)
131  vtor_bnd_type(iion)= profiles%VTOR_BND_TYPE(iion)
132  END DO ion_loop1
133 
134 
135 
136 ! +++ Set up profiles:
137  rho_loop1: DO irho =1,nrho
138  g2(irho) = geometry%G2(irho)
139 
140  te(irho) = profiles%TE(irho)
141  ne(irho) = profiles%NE(irho)
142 
143  ion_loop2: DO iion = 1,nion
144  ti(irho,iion) = profiles%TI(irho,iion)
145  ni(irho,iion) = profiles%NI(irho,iion)
146  vtor(irho,iion) = profiles%VTOR(irho,iion)
147  aion(iion) = profiles%MION(iion)
148  zion(iion) = profiles%ZION(iion)
149  END DO ion_loop2
150  if (te(irho).ne.te(irho)) write(*,*) 'Warning te is nan ', irho
151 
152 ! +++ Electron collisions:
153 ! determination of Coulomb logarithm:
154  IF(te(irho).GE.1.e1_r8) clog = 24.e0_r8 - 1.15e0_r8*log10(ne(irho)*cn) + 2.30e0_r8*log10(te(irho))
155  IF(te(irho).LT.1.e1_r8) clog = 23.e0_r8 - 1.15e0_r8*log10(ne(irho)*cn) + 3.45e0_r8*log10(te(irho))
156 
157 
158 ! electron collision time:
159  tau_e(irho) = (sqrt(2.d0*me)*(te(irho))**1.5) / 1.8d-19 / (ne(irho)*cn) / clog
160 
161 
162 ! Plasma electrical conductivity:
163  sigma(irho) = 1.96e0_r8 * e**2 *ne(irho)*cn * tau_e(irho) /me /cs
164 
165  END DO rho_loop1
166 
167 
168 
169 ! +++ Various ion exchange quantities:
170  rho_loop2: DO irho = 1,nrho
171  vie(irho) = 0.e0_r8
172  qie(irho) = 0.e0_r8
173 
174 
175 
176  ion_loop3: DO iion = 1,nion
177  vei(irho,iion) = 0.e0_r8
178  qei(irho,iion) = 0.e0_r8
179  vzi(irho,iion) = 0.e0_r8
180  qzi(irho,iion) = 0.e0_r8
181  uzi(irho,iion) = 0.e0_r8
182  wzi(irho,iion) = 0.e0_r8 !DPC 2009-01-19
183 
184  if (ti(irho,iion).ne.ti(irho,iion)) write(*,*) 'warning, ti is nan', irho, iion
185 
186 ! +++ Electron-Ion collisions:
187 ! determination of Coulomb logarithm:
188  IF(te(irho).GE.10.*zion(iion)**2) THEN
189  clog = 24.e0_r8 - 1.15e0_r8*log10(ne(irho)*cn) + 2.30e0_r8*log10(te(irho))
190  ELSE IF(te(irho).LT.10.*zion(iion)**2) THEN
191  clog = 23.e0_r8 - 1.15e0_r8*log10(ne(irho)*cn) + 3.45e0_r8*log10(te(irho))
192  ELSE
193  WRITE(*,*) 'Should not get here!'
194  WRITE(*,*) irho, te(irho)
195  pause
196  stop 'ERROR'
197  ENDIF
198 
199 ! determination of electron-ion collision time and energy exchange term:
200  tau_ei(irho,iion) = (te(irho)*mp*aion(iion) + ti(irho,iion)*me)**1.5 / 1.8d-19 &
201  / (sqrt(aion(iion)*me*mp)) / (ni(irho,iion)*cn) / zion(iion)**2 / clog
202 
203 
204 
205  vei(irho,iion) = 0.e0_r8
206 
207 !dy IF (TAU_EI(IRHO,IION).GT.0.e0_R8.AND.TE_BND_TYPE.NE.0.AND.TI_BND_TYPE(IION).NE.0) &
208  IF (tau_ei(irho,iion).GT.0.e0_r8) &
209 ! from electrons to ion component (IION):
210  vei(irho,iion) = ne(irho) / tau_ei(irho,iion)
211  qei(irho,iion) = vei(irho,iion) * te(irho)
212 
213 
214 ! from all ion components to electrons:
215  vie(irho) = vie(irho) + vei(irho,iion)
216  qie(irho) = qie(irho) + vei(irho,iion) * ti(irho,iion)
217 
218 
219 
220 ! +++ Ion-Ion collisions:
221  ion_loop4: DO iz = 1,nion
222  IF (iz.NE.iion) THEN
223  viz(irho,iion,iz) = 0.e0_r8
224 
225 
226 ! determination of Coulomb logarithm:
227  mzi = mp * aion(iion)*aion(iz) / (aion(iz)+aion(iion))
228 
229 
230  clog = 23.0d0 - log( zion(iion)*zion(iz) * (aion(iion)+aion(iz)) / (aion(iion)*ti(irho,iz)+aion(iz)*ti(irho,iion))) &
231  - log( sqrt(ni(irho,iion)*cn*zion(iion)**2./ti(irho,iion) + ni(irho,iz)*cn*zion(iz)**2./ti(irho,iz)) )
232 
233 
234 ! determination of ion-ion collision time and energy exchange term:
235  tau_zi(irho,iz) = (ti(irho,iion)*mp*aion(iz) + ti(irho,iz)*mp*aion(iion))**1.5 / 1.8d-19 &
236  / (sqrt(aion(iion)*mp*aion(iz)*mp)) / (ni(irho,iion)*cn)/zion(iion)**2/zion(iz)**2 / clog
237 
238 
239 
240 
241 ! ion-ion collision frequency:
242  viz(irho,iion,iz) = 0.e0_r8
243  wiz(irho,iion,iz) = 0.e0_r8
244 
245 !dy IF (TAU_ZI(IRHO,IZ).GT.0.e0_R8.AND.TI_BND_TYPE(IION).NE.0.AND.TI_BND_TYPE(IZ).NE.0) &
246  IF (tau_zi(irho,iz).GT.0.e0_r8) &
247  viz(irho,iion,iz) = ni(irho,iz) / tau_zi(irho,iz)
248 
249 !dy IF (TAU_ZI(IRHO,IZ).GT.0.e0_R8.AND.VTOR_BND_TYPE(IION).NE.0.AND.VTOR_BND_TYPE(IZ).NE.0) &
250  IF (tau_zi(irho,iz).GT.0.e0_r8) &
251  wiz(irho,iion,iz) = ni(irho,iz) / tau_zi(irho,iz) * mp*aion(iz)*cm * g2(irho)
252 
253 
254 ! total exchange terms, from all ion components to ion component (IION):
255  vzi(irho,iion) = vzi(irho,iion) + viz(irho,iion,iz)
256  qzi(irho,iion) = qzi(irho,iion) + viz(irho,iion,iz) * ti(irho,iz)
257  wzi(irho,iion) = wzi(irho,iion) + wiz(irho,iion,iz)
258  uzi(irho,iion) = uzi(irho,iion) + wiz(irho,iion,iz) * vtor(irho,iz)
259 
260  END IF
261 
262 
263 
264 ! +++ Collision quantities, output to the work flow:
265  collisions%VII(irho,iion,iz) = viz(irho,iion,iz)
266  collisions%WII(irho,iion,iz) = wiz(irho,iion,iz)
267 
268  END DO ion_loop4
269 
270  collisions%VEI(irho,iion) = vei(irho,iion)
271  collisions%QEI(irho,iion) = qei(irho,iion)
272  collisions%VZI(irho,iion) = vzi(irho,iion)
273  collisions%QZI(irho,iion) = qzi(irho,iion)
274  collisions%WZI(irho,iion) = wzi(irho,iion)
275  collisions%UZI(irho,iion) = uzi(irho,iion)
276 
277  END DO ion_loop3
278 
279  collisions%SIGMA(irho) = sigma(irho)
280  collisions%VIE(irho) = vie(irho)
281  collisions%QIE(irho) = qie(irho)
282 
283  END DO rho_loop2
284 
285 
286 
287 
288  RETURN
289 
290 
291 
292 
293 END SUBROUTINE plasma_collisions
294 
295 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
296 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
297 
298 
299 END MODULE plasma_collisionality
subroutine profiles(p0, rbphi, dp0, drbphi, a)
Definition: profiles.f90:1
This routine calculates the collision frquencies and various exchange terms determined by collisions...
subroutine plasma_collisions(GEOMETRY, PROFILES, COLLISIONS, ifail)
The module declares types of variables used in ETS (transport code)
Definition: ets_plasma.f90:8