ETS-Core  version:0.0.4-46-ge2d8
Core actors for the ETS-6
 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 (COREPROFILES, CORETRANSPORT)
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@euro-fusion.org !
16 ! !
17 ! Comments: output CORE_TRANSPORT IDS is !
18 ! allocated inside the module !
19 ! !
20 !-------------------------------------------------------!
21 
22  USE ids_schemas
23  USE ids_routines
24  USE imas_constants_module
26  USE ets_plasma
27  USE get_composition
28 
29 
30  IMPLICIT NONE
31 
32  INTEGER :: ifail
33 
34 ! +++ CPO types:
35  TYPE (ids_core_profiles) :: coreprofiles !input IDS with profiles
36  TYPE (ids_core_transport) :: coretransport !output IDS with transport (SIGMA)
37 
38 ! +++ ETS derived types:
39  TYPE (plasma_composition) :: composition
40 
41 
42 ! +++ Dimensions:
43  INTEGER (IDS_INT) :: ntime
44  INTEGER (IDS_INT) :: nmod
45  INTEGER (IDS_INT) :: nrho, irho
46 
47 
48 ! +++ Internal variables:
49  REAL (IDS_REAL) :: clog !Coulomb logarithm
50  REAL (IDS_REAL), ALLOCATABLE :: te(:)
51  REAL (IDS_REAL), ALLOCATABLE :: ne(:)
52  REAL (IDS_REAL), ALLOCATABLE :: tau_e(:)
53  REAL (IDS_REAL), ALLOCATABLE :: sigma(:)
54 
55 ! +++ Constants:
56  REAL (IDS_REAL), PARAMETER :: me = imas_constants%me*1e3_ids_real !electron mass [g]
57  REAL (IDS_REAL), PARAMETER :: e = imas_constants%ev*3e9_ids_real !elementary charge, [esu]
58  REAL (IDS_REAL), PARAMETER :: cn = 1.e-6_ids_real !density convergence from [m^-3] to [cm^-3]
59  REAL (IDS_REAL), PARAMETER :: cs = 9.e9_ids_real !conductivity convergence from [(Ohm*m)^-1] to [s^-1]
60 
61 
62 ! +++ Set dimensions:
63  nrho = SIZE(coreprofiles%profiles_1d(1)%grid%rho_tor_norm)
64 ! CALL GET_PROF_COMPOSITION (COREPROFILES, COMPOSITION) !!! TRY EMPTY COMPOSITION
65 
66 ! +++ Allocate output CPO:
67  ntime = 1
68  nmod = 1
69  CALL allocate_coretransport_ids(ntime, nmod, nrho, composition, coretransport)
70 
71 
72  coretransport%ids_properties%comment(1) = "Spitzer resistivity"
73  coretransport%ids_properties%source(1) = "spitzer_actor"
74  coretransport%ids_properties%homogeneous_time = 1
75 
76  coretransport%model(1)%identifier%name(1) = "neoclassical"
77  coretransport%model(1)%identifier%index = 5
78  coretransport%model(1)%identifier%description(1) = "Spitzer resistivity"
79 
80  coretransport%model(1)%flux_multiplier = 0.0_ids_real
81 
82  CALL ids_copy(coreprofiles%profiles_1d(1)%grid, coretransport%model(1)%profiles_1d(1)%grid_d)
83  CALL ids_copy(coreprofiles%profiles_1d(1)%grid, coretransport%model(1)%profiles_1d(1)%grid_v)
84  CALL ids_copy(coreprofiles%profiles_1d(1)%grid, coretransport%model(1)%profiles_1d(1)%grid_flux)
85 
86 !!$ CORETRANSPORT%model(1)%profiles_1d(1)%grid_d%rho_tor_norm = COREPROFILES%profiles_1d(1)%grid%rho_tor_norm
87 !!$ CORETRANSPORT%model(1)%profiles_1d(1)%grid_d%rho_tor = COREPROFILES%profiles_1d(1)%grid%rho_tor
88 !!$ CORETRANSPORT%model(1)%profiles_1d(1)%grid_d%psi = COREPROFILES%profiles_1d(1)%grid%psi
89 !!$ CORETRANSPORT%model(1)%profiles_1d(1)%grid_d%volume = COREPROFILES%profiles_1d(1)%grid%volume
90 !!$ CORETRANSPORT%model(1)%profiles_1d(1)%grid_d%area = COREPROFILES%profiles_1d(1)%grid%area
91 
92 
93 
94 ! +++ Set up profiles:
95  ALLOCATE (te(nrho))
96  ALLOCATE (ne(nrho))
97  ALLOCATE (tau_e(nrho))
98  ALLOCATE (sigma(nrho))
99  rho_loop1: DO irho =1,nrho
100  te(irho) = coreprofiles%profiles_1d(1)%electrons%temperature(irho)
101  ne(irho) = coreprofiles%profiles_1d(1)%electrons%density_thermal(irho)
102 
103 
104 ! +++ Electron collisions:
105 ! determination of Coulomb logarithm:
106  IF(te(irho).GE.10) clog = 24.e0_ids_real - 1.15e0_ids_real*log10(ne(irho)*cn) + 2.30e0_ids_real*log10(te(irho))
107  IF(te(irho).LT.10) clog = 23.e0_ids_real - 1.15e0_ids_real*log10(ne(irho)*cn) + 3.45e0_ids_real*log10(te(irho))
108 
109 
110 ! electron collision time:
111  tau_e(irho) = (sqrt(2.d0*me)*(te(irho))**1.5) / 1.8d-19 / (ne(irho)*cn) / clog
112 
113 
114 ! Plasma electrical conductivity:
115  sigma(irho) = 1.96e0_ids_real * e**2 *ne(irho)*cn * tau_e(irho) /me /cs
116 
117  END DO rho_loop1
118 
119  coretransport%model(1)%profiles_1d(1)%conductivity_parallel = sigma
120 
121  IF (ALLOCATED(te)) DEALLOCATE (te)
122  IF (ALLOCATED(ne)) DEALLOCATE (ne)
123  IF (ALLOCATED(tau_e)) DEALLOCATE (tau_e)
124  IF (ALLOCATED(sigma)) DEALLOCATE (sigma)
125 
126  RETURN
127 
128  END SUBROUTINE spitzer_resistivity
129 !-------------------------------------------------------!
130 !-------------------------------------------------------!
131 
132 
133 END MODULE spitzer
This module contains routines for allocation/deallocation if IDSs used in ETS.
subroutine allocate_coretransport_ids(NTIME, NMOD, NRHO, COMPOSITION, CORETRANSPORT)
This module contains routines for detecting plasma composition in IDSs.
The module defines derived types used by ETS6-CoreActor and subroutines to allocate and deallocate in...
Definition: ets_plasma.f90:26
subroutine spitzer_resistivity(COREPROFILES, CORETRANSPORT)
Definition: spitzer.f90:7