ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
fc2k_background_transport.f90
Go to the documentation of this file.
1 !-------------------------------------------------------!
2 !-------------------------------------------------------!
3 
4  SUBROUTINE background_transport (COREPROF, &
5  sigma, &
6  diff_ni, vconv_ni, &
7  diff_ne, vconv_ne, &
8  diff_ti, vconv_ti, &
9  diff_te, vconv_te, &
10  diff_vtor, vconv_vtor, &
11  diff_nz, vconv_nz, &
12  diff_tz, vconv_tz, &
13  coretransp)
14 
15 !-------------------------------------------------------!
16 ! This routine is used by the ETS workflow !
17 ! to fill background transport coefficients !
18 !-------------------------------------------------------!
19 ! Source: --- !
20 ! Developers: D.Kalupin !
21 ! Kontacts: Denis.Kalupin@efda.org !
22 ! !
23 ! Comments: output CORETRANSP CPO is !
24 ! allocated inside the module !
25 ! !
26 !-------------------------------------------------------!
27 
28  USE euitm_schemas
29  USE euitm_routines
31  USE copy_structures
32  USE itm_types
33  USE deallocate_structures
34 
35  IMPLICIT NONE
36 
37  INTEGER :: ifail
38 
39 ! +++ CPO derived types:
40  TYPE (type_coreprof), POINTER :: coreprof(:) !input CPO with internal ETS parameters profiles from previous time
41  TYPE (type_coretransp), POINTER :: coretransp(:) !output CPO with transport
42 
43 
44 ! +++ Dimensions:
45  INTEGER, PARAMETER :: nslice = 1 !number of CPO ocurancies in the work flow
46  INTEGER :: nrho !number of radial points (input, determined from COREPROF CPO)
47  INTEGER :: nion, iion !number of ion species (input, determined from COREPROF CPO)
48  INTEGER :: nimp, iimp !number of impurities (input)
49  INTEGER :: nnucl !number of nuclei species
50  INTEGER, ALLOCATABLE :: nzimp(:) !number of ionization states for each impurity
51  INTEGER :: nneut !number of neutrals species
52  INTEGER, ALLOCATABLE :: ncomp(:) !number of components for each neutral
53  INTEGER, ALLOCATABLE :: ntype(:) !number of types for each neutral
54 
55  REAL(R8) :: sigma
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 (coreprof(1)%rho_tor, dim=1)
66 
67 ! +++ Allocate output CPO:
68  CALL get_comp_dimensions(coreprof(1)%COMPOSITIONS, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp)
69  CALL allocate_coretransp_cpo(nslice, nrho, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, coretransp)
70  call deallocate_cpo(coretransp(1)%COMPOSITIONS)
71  CALL copy_cpo(coreprof(1)%COMPOSITIONS, coretransp(1)%COMPOSITIONS)
72 
73 
74 
75 ! +++ Save output in CPO:
76  coretransp(1)%time = coreprof(1)%time !time [s]
77 
78  coretransp(1)%VALUES(1)%rho_tor = coreprof(1)%rho_tor !rho [m]
79  coretransp(1)%VALUES(1)%rho_tor_norm = coreprof(1)%rho_tor/coreprof(1)%rho_tor(nrho)
80 
81  coretransp(1)%VALUES(1)%sigma = sigma
82  coretransp(1)%VALUES(1)%ne_transp%diff_eff(:,1) = diff_ne
83  coretransp(1)%VALUES(1)%ne_transp%vconv_eff(:,1) = vconv_ne
84  coretransp(1)%VALUES(1)%ne_transp%diff_eff(:,2) = 0.0_r8
85  coretransp(1)%VALUES(1)%ne_transp%vconv_eff(:,2) = 0.0_r8
86  coretransp(1)%VALUES(1)%ne_transp%diff_eff(:,3) = 0.0_r8
87  coretransp(1)%VALUES(1)%ne_transp%vconv_eff(:,3) = 0.0_r8
88  coretransp(1)%VALUES(1)%te_transp%diff_eff(:) = diff_te
89  coretransp(1)%VALUES(1)%te_transp%vconv_eff(:) = vconv_te
90 
91  DO iion = 1, nion
92  coretransp(1)%VALUES(1)%ni_transp%diff_eff(:,iion,1) = diff_ni(iion)
93  coretransp(1)%VALUES(1)%ni_transp%vconv_eff(:,iion,1) = vconv_ni(iion)
94  coretransp(1)%VALUES(1)%ni_transp%diff_eff(:,iion,2) = 0.0_r8
95  coretransp(1)%VALUES(1)%ni_transp%vconv_eff(:,iion,2) = 0.0_r8
96  coretransp(1)%VALUES(1)%ni_transp%diff_eff(:,iion,3) = 0.0_r8
97  coretransp(1)%VALUES(1)%ni_transp%vconv_eff(:,iion,3) = 0.0_r8
98  coretransp(1)%VALUES(1)%ti_transp%diff_eff(:,iion) = diff_ti(iion)
99  coretransp(1)%VALUES(1)%ti_transp%vconv_eff(:,iion) = vconv_ti(iion)
100  coretransp(1)%VALUES(1)%vtor_transp%diff_eff(:,iion) = diff_vtor(iion)
101  coretransp(1)%VALUES(1)%vtor_transp%vconv_eff(:,iion) = vconv_vtor(iion)
102  END DO
103 
104  DO iimp = 1, nimp
105  coretransp(1)%VALUES(1)%NZ_TRANSP(iimp)%diff_eff(:,:) = diff_nz(iimp)
106  coretransp(1)%VALUES(1)%NZ_TRANSP(iimp)%vconv_eff(:,:) = vconv_nz(iimp)
107  coretransp(1)%VALUES(1)%TZ_TRANSP(iimp)%diff_eff(:,:) = diff_tz(iimp)
108  coretransp(1)%VALUES(1)%TZ_TRANSP(iimp)%vconv_eff(:,:) = vconv_tz(iimp)
109  END DO
110 
111 
112 
113 ! +++ ADD IDENTIFIER TO OUTPUT CPO VALUES(1):
114  ALLOCATE (coretransp(1)%VALUES(1)%transportid%id(1))
115  ALLOCATE (coretransp(1)%VALUES(1)%transportid%description(1))
116  coretransp(1)%VALUES(1)%transportid%id = 'background'
117  coretransp(1)%VALUES(1)%transportid%flag = 11
118  coretransp(1)%VALUES(1)%transportid%description = 'Background transport level'
119 
120 
121 
122 
123  RETURN
124 
125  END SUBROUTINE background_transport
126 !-------------------------------------------------------!
127 !-------------------------------------------------------!
subroutine get_comp_dimensions(COMPOSITIONS, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP)
subroutine background_transport(COREPROF, SIGMA, 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, CORETRANSP)
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.