ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
spitzer.f90
Go to the documentation of this file.
1 MODULE spitzer
2 
3 CONTAINS
4 !-------------------------------------------------------!
5 !-------------------------------------------------------!
6 
7  SUBROUTINE spitzer_resistivity (COREPROF_IN, CORETRANSP_OUT)
8 
9 !-------------------------------------------------------!
10 ! This routine is used by the ETS workflow !
11 ! to calculate Spitzer resistivity !
12 !-------------------------------------------------------!
13 ! Source: --- !
14 ! Developers: D.Kalupin !
15 ! Kontacts: Denis.Kalupin@efda.org !
16 ! !
17 ! Comments: output CORETRANSP CPO is !
18 ! allocated inside the module !
19 ! !
20 !-------------------------------------------------------!
21 
22  USE itm_types
23  USE itm_constants
24  USE euitm_schemas
27 
28 
29  IMPLICIT NONE
30 
31  INTEGER :: ifail
32 
33 ! +++ CPO types:
34  TYPE (type_coreprof), POINTER :: coreprof_in(:) !input CPO with profiles
35  TYPE (type_coretransp), POINTER :: coretransp_out(:) !output CPO with transport (SIGMA)
36 
37 ! +++ Dimensions:
38  INTEGER, PARAMETER :: nslice = 1 !number of CPO ocurancies in the work flow
39  INTEGER :: nrho, irho !number of radial points (input, determined from COREPROF CPO)
40  INTEGER :: nnucl !number of nuclei species
41  INTEGER :: nion !number of ion species
42  INTEGER :: nimp !number of impurity species
43  INTEGER, ALLOCATABLE :: nzimp(:) !number of ionization states for each impurity
44  INTEGER :: nneut !number of neutrals species
45  INTEGER, ALLOCATABLE :: ncomp(:) !number of components for each neutral
46  INTEGER, ALLOCATABLE :: ntype(:) !number of types for each neutral
47 
48 ! +++ Internal variables:
49  REAL (R8) :: clog !Coulomb logarithm
50  REAL (R8), ALLOCATABLE :: te(:)
51  REAL (R8), ALLOCATABLE :: ne(:)
52  REAL (R8), ALLOCATABLE :: tau_e(:)
53  REAL (R8), ALLOCATABLE :: sigma(:)
54 
55 ! +++ Constants:
56  REAL (R8), PARAMETER :: me = itm_me*1e3_r8 !electron mass [g]
57  REAL (R8), PARAMETER :: e = itm_qe*3e9_r8 !elementary charge, [esu]
58  REAL (R8), PARAMETER :: cn = 1.e-6_r8 !density convergence from [m^-3] to [cm^-3]
59  REAL (R8), PARAMETER :: cs = 9.e9_r8 !conductivity convergence from [(Ohm*m)^-1] to [s^-1]
60 
61 
62 ! +++ Set dimensions:
63  nrho = SIZE (coreprof_in(1)%rho_tor)
64  CALL get_comp_dimensions(coreprof_in(1)%COMPOSITIONS, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp)
65 
66 ! +++ Allocate output CPO:
67  CALL allocate_coretransp_cpo(nslice, nrho, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, coretransp_out)
68  coretransp_out(1)%VALUES(1)%rho_tor = coreprof_in(1)%rho_tor
69 
70 ! +++ Set up profiles:
71  ALLOCATE (te(nrho))
72  ALLOCATE (ne(nrho))
73  ALLOCATE (tau_e(nrho))
74  ALLOCATE (sigma(nrho))
75  rho_loop1: DO irho =1,nrho
76  te(irho) = coreprof_in(1)%TE%value(irho)
77  ne(irho) = coreprof_in(1)%NE%value(irho)
78 
79 
80 ! +++ Electron collisions:
81 ! determination of Coulomb logarithm:
82  IF(te(irho).GE.10) clog = 24.e0_r8 - 1.15e0_r8*log10(ne(irho)*cn) + 2.30e0_r8*log10(te(irho))
83  IF(te(irho).LT.10) clog = 23.e0_r8 - 1.15e0_r8*log10(ne(irho)*cn) + 3.45e0_r8*log10(te(irho))
84 
85 
86 ! electron collision time:
87  tau_e(irho) = (sqrt(2.d0*me)*(te(irho))**1.5) / 1.8d-19 / (ne(irho)*cn) / clog
88 
89 
90 ! Plasma electrical conductivity:
91  sigma(irho) = 1.96e0_r8 * e**2 *ne(irho)*cn * tau_e(irho) /me /cs
92 
93  END DO rho_loop1
94 
95  coretransp_out(1)%VALUES(1)%sigma = sigma
96 
97 ! +++ ADD IDENTIFIER TO OUTPUT CPO VALUES(1):
98  ALLOCATE (coretransp_out(1)%VALUES(1)%transportid%id(1))
99  ALLOCATE (coretransp_out(1)%VALUES(1)%transportid%description(1))
100  coretransp_out(1)%VALUES(1)%transportid%id = 'spitzer'
101  coretransp_out(1)%VALUES(1)%transportid%flag = 14
102  coretransp_out(1)%VALUES(1)%transportid%description = 'Spitzer Resistivity'
103 
104 
105  IF (ALLOCATED(te)) DEALLOCATE (te)
106  IF (ALLOCATED(ne)) DEALLOCATE (ne)
107  IF (ALLOCATED(tau_e)) DEALLOCATE (tau_e)
108  IF (ALLOCATED(sigma)) DEALLOCATE (sigma)
109 
110  RETURN
111 
112  END SUBROUTINE spitzer_resistivity
113 !-------------------------------------------------------!
114 !-------------------------------------------------------!
115 
116 
117 END MODULE spitzer
subroutine spitzer_resistivity(COREPROF_IN, CORETRANSP_OUT)
Definition: spitzer.f90:7
subroutine get_comp_dimensions(COMPOSITIONS, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP)
This routine calculates the collision frquencies and various exchange terms determined by collisions...
This module contains routines for allocation/deallocation if CPOs used in ETS.
subroutine allocate_coretransp_cpo(NSLICE, NRHO, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP, CORETRANSP)
This routine allocates CORETRANSP CPO.