ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
fc2k_imp4dv.f90
Go to the documentation of this file.
1 SUBROUTINE fc2k_imp4dv(EQUILIBRIUM, COREPROF, CORETRANSP_IN, CORETRANSP_OUT)
2 
3  USE euitm_schemas
4  USE itm_constants
6  USE itm_types
7  USE copy_structures
8  USE deallocate_structures
9 
10 
11  IMPLICIT NONE
12 
13  TYPE (type_equilibrium), POINTER :: equilibrium(:)
14  TYPE (type_coreprof), POINTER :: coreprof(:)
15  TYPE (type_coretransp), POINTER :: coretransp_in(:)
16  TYPE (type_coretransp), POINTER :: coretransp_out(:)
17 
18  INTEGER :: i
19  INTEGER :: npsi, nrho_prof
20 
21  INTEGER, PARAMETER :: nslice = 1 !number of CPO ocurancies in the work flow
22  INTEGER :: nrho !number of radial points (input, determined from COREPROF CPO)
23  INTEGER :: nion, ion !number of ion species (input, determined from COREPROF CPO)
24  INTEGER :: nimp !number of impurities (input)
25  INTEGER :: nnucl !number of nuclei species
26  INTEGER, ALLOCATABLE :: nzimp(:) !number of ionization states for each impurity
27  INTEGER :: nneut !number of neutrals species
28  INTEGER, ALLOCATABLE :: ncomp(:) !number of components for each neutral
29  INTEGER, ALLOCATABLE :: ntype(:) !number of types for each neutral
30 
31 
32 
33 
34 
35 
36  REAL(R8) :: a00,b00,r00,rho_tor_max
37 
38  REAL(R8) :: nni,tti,rlni,rlti,llni,llti
39  REAL(R8) :: ffi,ggi,diffi,chii,vconvi,yconvi
40 
41  REAL(R8) :: nne,tte,rlne,rlte,llne,llte
42  REAL(R8) :: ffe,gge,diffe,chie,vconve,yconve
43 
44  REAL(R8), ALLOCATABLE :: gm3(:),gm7(:)
45 
46  REAL(R8), ALLOCATABLE :: rltix(:,:),ffix(:,:), ggix(:,:)
47  REAL(R8), ALLOCATABLE :: nnix(:,:), ttix(:,:), rlnix(:,:)
48 
49  REAL(R8), ALLOCATABLE :: rltex(:), ffex(:), ggex(:)
50  REAL(R8), ALLOCATABLE :: nnex(:), ttex(:), rlnex(:)
51 
52  REAL(R8), ALLOCATABLE :: rho_prof(:), rho_transp(:)
53 
54 
55 
56 
57 ! +++ grid sizes
58  npsi = SIZE(equilibrium(1)%profiles_1d%rho_tor)
59  nrho_prof = SIZE(coreprof(1)%rho_tor)
60  nrho = SIZE(coretransp_in(1)%VALUES(1)%rho_tor)
61 
62 
63 ! +++ Allocate output CPO:
64  CALL get_comp_dimensions(coretransp_in(1)%COMPOSITIONS, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp)
65  CALL allocate_coretransp_cpo(nslice, nrho, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, coretransp_out)
66  call deallocate_cpo(coretransp_out(1)%COMPOSITIONS)
67  CALL copy_cpo(coretransp_in(1)%COMPOSITIONS, coretransp_out(1)%COMPOSITIONS)
68 
69 
70 
71  ALLOCATE ( gm3(nrho))
72  ALLOCATE ( gm7(nrho))
73 
74  ALLOCATE (rho_prof(nrho_prof))
75  ALLOCATE (rho_transp(nrho))
76 
77  ALLOCATE ( nnix(nrho,nion))
78  ALLOCATE ( ttix(nrho,nion))
79  ALLOCATE (rlnix(nrho,nion))
80  ALLOCATE (rltix(nrho,nion))
81  ALLOCATE ( ffix(nrho,nion))
82  ALLOCATE ( ggix(nrho,nion))
83 
84  ALLOCATE ( nnex(nrho))
85  ALLOCATE ( ttex(nrho))
86  ALLOCATE (rlnex(nrho))
87  ALLOCATE (rltex(nrho))
88  ALLOCATE ( ffex(nrho))
89  ALLOCATE ( ggex(nrho))
90 
91 
92  rho_prof = coreprof(1)%rho_tor
93  rho_transp = coretransp_in(1)%VALUES(1)%rho_tor
94 
95 
96  nnix = 0.0_r8
97  ttix = 0.0_r8
98  rlnix = 0.0_r8
99  rltix = 0.0_r8
100  ffix = 0.0_r8
101  ggix = 0.0_r8
102 
103  nnex = 0.0_r8
104  ttex = 0.0_r8
105  rlnex = 0.0_r8
106  rltex = 0.0_r8
107  ffex = 0.0_r8
108  ggex = 0.0_r8
109 
110 
111 
112 ! +++ Get geometry:
113 
114  r00 = equilibrium(1)%global_param%toroid_field%r0
115 
116  IF (ASSOCIATED(equilibrium(1)%profiles_1d%gm3)) THEN
117  CALL l3interp( equilibrium(1)%profiles_1d%gm3, equilibrium(1)%profiles_1d%rho_tor, npsi, &
118  gm3, rho_transp, nrho)
119  ELSE
120  gm3=1.0
121  END IF
122 
123  IF (ASSOCIATED(equilibrium(1)%profiles_1d%gm7)) THEN
124  CALL l3interp( equilibrium(1)%profiles_1d%gm7, equilibrium(1)%profiles_1d%rho_tor, npsi, &
125  gm7, rho_transp, nrho)
126  ELSE
127  gm7=1.0
128  END IF
129 
130 
131 ! +++ Get parameters:
132 
133  CALL l3interp( coreprof(1)%ne%value, rho_prof, nrho_prof, &
134  nnex, rho_transp, nrho)
135  CALL l3interp( coreprof(1)%te%value, rho_prof, nrho_prof, &
136  ttex, rho_transp, nrho)
137  CALL l3deriv( coreprof(1)%ne%value, rho_prof, nrho_prof, &
138  rlnex, rho_transp, nrho)
139  CALL l3deriv( coreprof(1)%te%value, rho_prof, nrho_prof, &
140  rltex, rho_transp, nrho)
141 
142  ffex = coretransp_in(1)%VALUES(1)%ne_transp%flux
143  ggex = coretransp_in(1)%VALUES(1)%te_transp%flux
144 
145 
146 
147  DO ion=1,nion
148  CALL l3interp( coreprof(1)%ni%value(:,ion), rho_prof, nrho_prof, &
149  nnix(:,ion), rho_transp, nrho)
150  CALL l3interp( coreprof(1)%ti%value(:,ion), rho_prof, nrho_prof, &
151  ttix(:,ion), rho_transp, nrho)
152  CALL l3deriv( coreprof(1)%ni%value(:,ion), rho_prof, nrho_prof, &
153  rlnix(:,ion), rho_transp, nrho)
154  CALL l3deriv( coreprof(1)%ti%value(:,ion), rho_prof, nrho_prof, &
155  rltix(:,ion), rho_transp, nrho)
156 
157  ffix(:,ion) = coretransp_in(1)%VALUES(1)%ni_transp%flux(:,ion)
158  ggix(:,ion) = coretransp_in(1)%VALUES(1)%ti_transp%flux(:,ion)
159 
160  END DO
161 
162 
163 
164 ! +++ assume fluxes get Ds and Vs
165 
166  DO i=1,nrho
167 
168  tte = ttex(i)
169  nne = nnex(i)
170  rlne =-rlnex(i)/nne
171  rlte =-rltex(i)/tte
172  ffe = ffex(i)/nne
173  gge = ggex(i)/(nne*itm_ev*tte)
174 
175  llne = 1./max(1./r00, abs(rlne))
176  llte = 1./max(1./r00, abs(rlte))
177 
178  diffe = abs(ffe)*llne
179  chie = abs(gge)*llte
180 
181  diffe = max(diffe, 0.2_r8*chie)
182  chie = max(chie, 0.2_r8*diffe)
183 
184  vconve = ffe - diffe*rlne
185  yconve = gge - chie*rlte
186 
187  diffe = diffe/gm3(i)
188  chie = chie/gm3(i)
189 
190  vconve = vconve/gm7(i)
191  yconve = yconve/gm7(i)
192 
193  coretransp_out(1)%VALUES(1)%ne_transp%diff_eff(i,2) = diffe
194  coretransp_out(1)%VALUES(1)%te_transp%diff_eff(i) = chie
195  coretransp_out(1)%VALUES(1)%ne_transp%vconv_eff(i,2) = vconve
196  coretransp_out(1)%VALUES(1)%te_transp%vconv_eff(i) = yconve
197 
198 
199  DO ion=1,nion
200 
201  tti = ttix(i,ion)
202  nni = nnix(i,ion)
203  rlni =-rlnix(i,ion)/nni
204  rlti =-rltix(i,ion)/tti
205  ffi = ffix(i,ion)/nni
206  ggi = ggix(i,ion)/(nni*itm_ev*tti)
207 
208  llni = 1./max(1./r00, abs(rlni))
209  llti = 1./max(1./r00, abs(rlti))
210 
211  diffi = abs(ffi)*llni
212  chii = abs(ggi)*llti
213 
214  diffi = max(diffi, 0.2_r8*chii)
215  chii = max(chii, 0.2_r8*diffi)
216 
217  vconvi = ffi - diffi*rlni
218  yconvi = ggi - chii*rlti
219 
220  diffi = diffi/gm3(i)
221  chii = chii/gm3(i)
222 
223  vconvi = vconvi/gm7(i)
224  yconvi = yconvi/gm7(i)
225 
226  coretransp_out(1)%VALUES(1)%ni_transp%diff_eff(i,ion,2) = diffi
227  coretransp_out(1)%VALUES(1)%ti_transp%diff_eff(i,ion) = chii
228  coretransp_out(1)%VALUES(1)%ni_transp%vconv_eff(i,ion,2) = vconvi
229  coretransp_out(1)%VALUES(1)%ti_transp%vconv_eff(i,ion) = yconvi
230  END DO
231 
232  END DO
233 
234 
235 
236 
237 ! +++ time
238 
239  coretransp_out(1)%time = coretransp_in(1)%time
240  coretransp_out(1)%VALUES(1)%rho_tor = rho_transp
241  coretransp_out(1)%VALUES(1)%rho_tor_norm = rho_transp/rho_transp(nrho)
242 
243 
244 ! +++ clean up
245 
246  DEALLOCATE(gm3)
247  DEALLOCATE(gm7)
248 
249  DEALLOCATE(nnix)
250  DEALLOCATE(ttix)
251  DEALLOCATE(rlnix)
252  DEALLOCATE(rltix)
253  DEALLOCATE(ffix)
254  DEALLOCATE(ggix)
255 
256  DEALLOCATE(nnex)
257  DEALLOCATE(ttex)
258  DEALLOCATE(rlnex)
259  DEALLOCATE(rltex)
260  DEALLOCATE(ffex)
261  DEALLOCATE(ggex)
262 
263  DEALLOCATE(rho_prof)
264  DEALLOCATE(rho_transp)
265 
266  RETURN
267 
268 END SUBROUTINE fc2k_imp4dv
subroutine l3deriv(y_in, x_in, nr_in, dydx_out, x_out, nr_out)
Definition: l3interp.f90:59
subroutine get_comp_dimensions(COMPOSITIONS, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP)
subroutine l3interp(y_in, x_in, nr_in, y_out, x_out, nr_out)
Definition: l3interp.f90:1
This module contains routines for allocation/deallocation if CPOs used in ETS.
subroutine fc2k_imp4dv(EQUILIBRIUM, COREPROF, CORETRANSP_IN, CORETRANSP_OUT)
Definition: fc2k_imp4dv.f90:1
subroutine allocate_coretransp_cpo(NSLICE, NRHO, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP, CORETRANSP)
This routine allocates CORETRANSP CPO.