ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
ets_start.f90
Go to the documentation of this file.
1 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
2 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
3 MODULE ets_start
4 
5 
6 CONTAINS
7 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
8 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
9  SUBROUTINE etsstart &
10 !PARAMETERS & CPOs_IN:
11  (solver, equilibrium_in, coreprof_in, &
12 !CPOs_OUT:
13  coreprof_out, coretransp_out, coresource_out, &
14  coreimpur_out, corefast_out, &
15  coreneutrals_out, neoclassic_out, &
16  equilibrium_out, toroidfield_out, &
17 !BOUNDARY_CONDITIONS:
18  psi_bnd_type, ne_bnd_type, ni_bnd_type, &
19  ti_bnd_type, te_bnd_type, vtor_bnd_type, &
20  imp_bnd_type, n0_bnd_type, t0_bnd_type, &
21 !
22  psi_bnd_value, ne_bnd_value, ni_bnd_value, &
23  ti_bnd_value, te_bnd_value, vtor_bnd_value, &
24  imp_bnd_value, n0_bnd_value, t0_bnd_value, &
25 !SPACE_RESOLUTION:
26  nrho, npsi, ndim1, ndim2, npoints)
27 
28 !-------------------------------------------------------!
29 ! This routine generates the RHO grid for ETS !
30 ! and defines the number of ion species and saves !
31 ! it in COREPROF CPO. !
32 !-------------------------------------------------------!
33 ! Source: --- !
34 ! Developers: D.Kalupin !
35 ! Kontacts: D.Kalupin@fz-juelich.de !
36 ! !
37 ! Comments: --- !
38 ! !
39 !-------------------------------------------------------!
40 
41 
42 ! +++ Declaration of variables:
44  USE euitm_schemas
45  USE itm_types
46  USE copy_structures
47  USE deallocate_structures
48 
49 
50  IMPLICIT NONE
51 
52 
53 ! +++ CPO derived types:
54  TYPE (type_coreprof), POINTER :: coreprof_in(:)
55  TYPE (type_equilibrium), POINTER :: equilibrium_in(:)
56 
57  TYPE (type_coreprof), POINTER :: coreprof_out(:)
58  TYPE (type_coretransp), POINTER :: coretransp_out(:)
59  TYPE (type_coresource), POINTER :: coresource_out(:)
60  TYPE (type_coreimpur), POINTER :: coreimpur_out(:)
61  TYPE (type_corefast), POINTER :: corefast_out(:)
62  TYPE (type_coreneutrals),POINTER :: coreneutrals_out(:)
63  TYPE (type_equilibrium), POINTER :: equilibrium_out(:)
64  TYPE (type_toroidfield), POINTER :: toroidfield_out(:)
65 ! TYPE (TYPE_COMPOSITIONC),POINTER :: COMPOSITIONC_OUT(:)
66  TYPE (type_neoclassic), POINTER :: neoclassic_out(:)
67 
68 ! +++ General settings:
69  REAL (R8) :: rhob !boundary value of RHO
70  INTEGER :: solver
71 
72 
73 ! +++ Dimensions:
74  INTEGER :: nrho, irho
75  INTEGER :: nnucl, inucl !number of nuclei species
76  INTEGER :: nion, iion !number of ion species
77  INTEGER :: nimp, iimp !number of impurity species
78  INTEGER, ALLOCATABLE :: nzimp(:) !number of ionization states for each impurity
79  INTEGER :: izimp
80  INTEGER :: nneut, ineut !number of neutrals species
81  INTEGER, ALLOCATABLE :: ncomp(:) !number of components for each neutral
82  INTEGER :: icomp
83  INTEGER, ALLOCATABLE :: ntype(:) !number of types for each neutral
84  INTEGER :: itype
85  INTEGER :: npsi !number of points for equilibrium 1-D arrays
86  INTEGER :: ndim1 !number of points for equilibrium 2-D arrays, first dimension
87  INTEGER :: ndim2 !number of points for equilibrium 2-D arrays, second dimension
88  INTEGER :: npoints !number of points for equilibrium boundary
89 
90 
91 ! +++ Local:
92  INTEGER :: psi_bnd_type
93  REAL (R8) :: psi_bnd_value(3)
94  INTEGER :: te_bnd_type
95  REAL (R8) :: te_bnd_value(3)
96  INTEGER :: ne_bnd_type
97  REAL (R8) :: ne_bnd_value(3)
98  INTEGER, ALLOCATABLE :: ni_bnd_type(:)
99  REAL (R8), ALLOCATABLE :: ni_bnd_value(:,:)
100  INTEGER, ALLOCATABLE :: ti_bnd_type(:)
101  REAL (R8), ALLOCATABLE :: ti_bnd_value(:,:)
102  INTEGER, ALLOCATABLE :: vtor_bnd_type(:)
103  REAL (R8), ALLOCATABLE :: vtor_bnd_value(:,:)
104 
105  INTEGER, ALLOCATABLE :: imp_bnd_type(:,:)
106  REAL (R8), ALLOCATABLE :: imp_bnd_value(:,:,:)
107 
108  INTEGER, ALLOCATABLE :: n0_bnd_type(:,:)
109  REAL (R8), ALLOCATABLE :: n0_bnd_value(:,:,:)
110  INTEGER, ALLOCATABLE :: t0_bnd_type(:,:)
111  REAL (R8), ALLOCATABLE :: t0_bnd_value(:,:,:)
112 
113  REAL (R8), ALLOCATABLE :: rho(:)
114  REAL (R8), ALLOCATABLE :: rhon(:)
115 
116 
117  INTEGER, PARAMETER :: nslice = 1
118  INTEGER :: i, neut_flag
119 
120 
121 
122 
123 
124  !----------------------------------------------------------------------!
125  ! Allocation of output CPOs !
126  !----------------------------------------------------------------------!
127  CALL get_comp_dimensions(coreprof_in(1)%COMPOSITIONS, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp)
128 
129  CALL allocate_coreprof_cpo(nslice, nrho, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, coreprof_out )
130  CALL allocate_coretransp_cpo(nslice, nrho, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, coretransp_out )
131  CALL allocate_corefast_cpo(nslice, nrho, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, corefast_out )
132  CALL allocate_coresource_cpo(nslice, nrho, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, coresource_out )
133  CALL allocate_coreneutrals_cpo(nslice, nrho, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, coreneutrals_out)
134  CALL allocate_coreimpur_cpo(nslice, nrho, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, coreimpur_out )
135  CALL allocate_neoclassic_cpo(nslice, nrho, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, neoclassic_out )
136  CALL allocate_toroidfield_cpo(nslice, toroidfield_out )
137  ALLOCATE (equilibrium_out(1))
138  CALL copy_cpo(equilibrium_in(1), equilibrium_out(1))
139 
140  !----------------------------------------------------------------------!
141  ! Set up starting time for all CPOs !
142  !----------------------------------------------------------------------!
143  coreprof_out(1)%time = equilibrium_in(1)%time
144  coretransp_out(1)%time = equilibrium_in(1)%time
145  corefast_out(1)%time = equilibrium_in(1)%time
146  coresource_out(1)%time = equilibrium_in(1)%time
147  IF(nimp.GT.0) coreimpur_out(1)%time = equilibrium_in(1)%time
148  IF(nneut.GT.0) coreneutrals_out(1)%time = equilibrium_in(1)%time
149  toroidfield_out(1)%time = equilibrium_in(1)%time
150 
151 
152 
153  !----------------------------------------------------------------------!
154  ! Set up equidistant rho grid for all CPOs !
155  !----------------------------------------------------------------------!
156  ALLOCATE (rho(nrho))
157  ALLOCATE (rhon(nrho))
158 
159  rhob = equilibrium_in(1)%profiles_1d%rho_tor(SIZE(equilibrium_in(1)%profiles_1d%rho_tor))
160 
161  rho_loop1: DO irho=1,nrho
162  rho(irho) = rhob/(nrho-1)*(irho-1)
163  rhon(irho) = real(irho-1, kind=r8)/(nrho-1)
164  IF (solver.EQ.4.AND.irho.NE.1.AND.irho.NE.nrho) THEN
165  rhon(irho) = 1.0_r8/(nrho-2)*(irho-2)+0.5_r8/(nrho-2)
166  rho(irho) = rhon(irho) * rhob
167  END IF
168  END DO rho_loop1
169 
170  coreprof_out(1)%rho_tor = rho
171  coretransp_out(1)%VALUES(1)%rho_tor = rho
172  corefast_out(1)%VALUES(1)%rho_tor = rho
173  coresource_out(1)%VALUES(1)%rho_tor = rho
174  IF(nimp.GT.0) coreimpur_out(1)%rho_tor = rho
175  IF(nneut.GT.0) coreneutrals_out(1)%rho_tor = rho
176  ALLOCATE (neoclassic_out(1)%rho_tor(nrho))
177  neoclassic_out(1)%rho_tor = rho
178 
179 
180  coreprof_out(1)%rho_tor_norm = rhon
181  coretransp_out(1)%VALUES(1)%rho_tor_norm = rhon
182  corefast_out(1)%VALUES(1)%rho_tor_norm = rhon
183  coresource_out(1)%VALUES(1)%rho_tor_norm = rhon
184  IF(nimp.GT.0) coreimpur_out(1)%rho_tor_norm = rhon
185  IF(nneut.GT.0) coreneutrals_out(1)%rho_tor_norm= rhon
186  ALLOCATE (neoclassic_out(1)%rho_tor_norm(nrho))
187  neoclassic_out(1)%rho_tor_norm = rhon
188 
189 
190 
191 
192 
193  !----------------------------------------------------------------------!
194  ! Set up PLASMA composition !
195  !----------------------------------------------------------------------!
196  CALL deallocate_cpo(coreprof_out(1)%COMPOSITIONS)
197  CALL copy_cpo(coreprof_in(1)%COMPOSITIONS, coreprof_out(1)%COMPOSITIONS)
198  CALL deallocate_cpo(coretransp_out(1)%COMPOSITIONS)
199  CALL copy_cpo(coreprof_in(1)%COMPOSITIONS, coretransp_out(1)%COMPOSITIONS)
200  CALL deallocate_cpo(corefast_out(1)%COMPOSITIONS)
201  CALL copy_cpo(coreprof_in(1)%COMPOSITIONS, corefast_out(1)%COMPOSITIONS)
202  CALL deallocate_cpo(coresource_out(1)%COMPOSITIONS)
203  CALL copy_cpo(coreprof_in(1)%COMPOSITIONS, coresource_out(1)%COMPOSITIONS)
204  IF(nneut.GT.0) THEN
205  CALL deallocate_cpo(coreneutrals_out(1)%COMPOSITIONS)
206  CALL copy_cpo(coreprof_in(1)%COMPOSITIONS, coreneutrals_out(1)%COMPOSITIONS)
207  ENDIF
208 !PIS IF(NIMP.GT.0) THEN
209  CALL deallocate_cpo(coreimpur_out(1)%COMPOSITIONS)
210  CALL copy_cpo(coreprof_in(1)%COMPOSITIONS, coreimpur_out(1)%COMPOSITIONS)
211 !PIS ENDIF
212  CALL deallocate_cpo(neoclassic_out(1)%COMPOSITIONS)
213  CALL copy_cpo(coreprof_in(1)%COMPOSITIONS, neoclassic_out(1)%COMPOSITIONS)
214 
215 
216 
217 
218 
219  !----------------------------------------------------------------------!
220  ! Set up Impurity charge states !
221  !----------------------------------------------------------------------!
222  IF(nimp.GT.0) THEN
223  DO iimp = 1,nimp
224  DO izimp = 1,nzimp(iimp)
225  coreimpur_out(1)%IMPURITY(iimp)%z(:,izimp) = (coreimpur_out(1)%COMPOSITIONS%IMPURITIES(iimp)%zmin(izimp) + &
226  coreimpur_out(1)%COMPOSITIONS%IMPURITIES(iimp)%zmax(izimp) )/2.0_r8
227  coreimpur_out(1)%IMPURITY(iimp)%zsq(:,izimp) = coreimpur_out(1)%IMPURITY(iimp)%z(:,izimp)**2
228  END DO
229  END DO
230  ENDIF
231 
232 
233 
234 
235  !----------------------------------------------------------------------!
236  ! Set up boundary condition type and value for main plasma !
237  !----------------------------------------------------------------------!
238 
239  coreprof_out(1)%psi%boundary%type = psi_bnd_type
240  coreprof_out(1)%te%boundary%type = te_bnd_type
241  coreprof_out(1)%ne%boundary%type = ne_bnd_type
242  coreprof_out(1)%ni%boundary%type = ni_bnd_type
243  coreprof_out(1)%ti%boundary%type = ti_bnd_type
244  coreprof_out(1)%vtor%boundary%type = vtor_bnd_type
245 
246  coreprof_out(1)%psi%boundary%value = psi_bnd_value
247  coreprof_out(1)%te%boundary%value = te_bnd_value
248  coreprof_out(1)%ne%boundary%value = ne_bnd_value
249  coreprof_out(1)%ni%boundary%value = ni_bnd_value
250  coreprof_out(1)%ti%boundary%value = ti_bnd_value
251  coreprof_out(1)%vtor%boundary%value = vtor_bnd_value
252 
253  coreprof_out(1)%psi%flag = 0
254  coreprof_out(1)%te%flag = 0
255  coreprof_out(1)%ne%flag = 0
256  coreprof_out(1)%ni%flag = 0
257  coreprof_out(1)%ti%flag = 0
258  coreprof_out(1)%vtor%flag = 0
259 
260  IF (psi_bnd_type.GE.1.AND.psi_bnd_type.LE.5) &
261  coreprof_out(1)%psi%flag = 2
262  IF (psi_bnd_type.EQ.6) &
263  coreprof_out(1)%psi%flag = 3
264  IF (psi_bnd_type.EQ.7) &
265  coreprof_out(1)%psi%flag = 1
266 
267  IF (ne_bnd_type.GE.1.AND.ne_bnd_type.LE.5) &
268  coreprof_out(1)%ne%flag = 2
269  IF (ne_bnd_type.EQ.6) &
270  coreprof_out(1)%ne%flag = 3
271  IF (ne_bnd_type.EQ.7) &
272  coreprof_out(1)%ne%flag = 1
273 
274  IF (te_bnd_type.GE.1.AND.te_bnd_type.LE.5) &
275  coreprof_out(1)%te%flag = 2
276  IF (te_bnd_type.EQ.6) &
277  coreprof_out(1)%te%flag = 3
278  IF (te_bnd_type.EQ.7) &
279  coreprof_out(1)%te%flag = 1
280 
281  DO iion = 1, nion
282 
283  IF (ni_bnd_type(iion).GE.1.AND.ni_bnd_type(iion).LE.5) &
284  coreprof_out(1)%ni%flag(iion) = 2
285  IF (ni_bnd_type(iion).EQ.6) &
286  coreprof_out(1)%ni%flag(iion) = 3
287  IF (ni_bnd_type(iion).EQ.7) &
288  coreprof_out(1)%ni%flag(iion) = 1
289 
290  IF (ti_bnd_type(iion).GE.1.AND.ti_bnd_type(iion).LE.5) &
291  coreprof_out(1)%ti%flag(iion) = 2
292  IF (ti_bnd_type(iion).EQ.6) &
293  coreprof_out(1)%ti%flag(iion) = 3
294  IF (ti_bnd_type(iion).EQ.7) &
295  coreprof_out(1)%ti%flag(iion) = 1
296 
297  IF (vtor_bnd_type(iion).GE.1.AND.vtor_bnd_type(iion).LE.5) &
298  coreprof_out(1)%VTOR%flag(iion) = 2
299  IF (vtor_bnd_type(iion).EQ.6) &
300  coreprof_out(1)%vtor%flag(iion) = 3
301  IF (vtor_bnd_type(iion).EQ.7) &
302  coreprof_out(1)%vtor%flag(iion) = 1
303 
304  END DO
305 
306  !----------------------------------------------------------------------!
307  ! Set up boundary condition type and value for impurities !
308  !----------------------------------------------------------------------!
309 
310  IF(nimp.GE.1) THEN
311  DO iimp = 1,nimp
312  DO izimp = 1,nzimp(iimp)
313  coreimpur_out(1)%IMPURITY(iimp)%boundary%type(izimp) = imp_bnd_type(iimp,izimp)
314  coreimpur_out(1)%IMPURITY(iimp)%boundary%value(:,izimp) = imp_bnd_value(iimp,:,izimp)
315  END DO
316  END DO
317  DEALLOCATE(imp_bnd_type, imp_bnd_value)
318  ENDIF
319 
320  DEALLOCATE(ni_bnd_type, ti_bnd_type, vtor_bnd_type)
321  DEALLOCATE(ni_bnd_value, ti_bnd_value, vtor_bnd_value)
322 
323 
324  !----------------------------------------------------------------------!
325  ! Set up boundary condition type and value for neutrals !
326  !----------------------------------------------------------------------!
327 
328  IF(nneut.GE.1) THEN
329  DO ineut = 1, nneut
330  DO itype = 1, ntype(ineut)
331  coreneutrals_out(1)%PROFILES(ineut)%NEUTRALTYPE(itype)%n0%boundary%type = n0_bnd_type(ineut,itype)
332  coreneutrals_out(1)%PROFILES(ineut)%NEUTRALTYPE(itype)%t0%boundary%type = t0_bnd_type(ineut,itype)
333  coreneutrals_out(1)%PROFILES(ineut)%NEUTRALTYPE(itype)%v0%toroidal%boundary%type = 0
334  coreneutrals_out(1)%PROFILES(ineut)%NEUTRALTYPE(itype)%v0%poloidal%boundary%type = 0
335 
336  coreneutrals_out(1)%PROFILES(ineut)%NEUTRALTYPE(itype)%n0%boundary%value(:) = n0_bnd_value(ineut,:,itype)
337  coreneutrals_out(1)%PROFILES(ineut)%NEUTRALTYPE(itype)%t0%boundary%value(:) = t0_bnd_value(ineut,:,itype)
338  coreneutrals_out(1)%PROFILES(ineut)%NEUTRALTYPE(itype)%v0%toroidal%boundary%value = 0.0_r8
339  coreneutrals_out(1)%PROFILES(ineut)%NEUTRALTYPE(itype)%v0%poloidal%boundary%value = 0.0_r8
340  ENDDO
341  ENDDO
342  DEALLOCATE(n0_bnd_type, t0_bnd_type, n0_bnd_value, t0_bnd_value)
343  ENDIF
344 
345  DEALLOCATE(rho, rhon)
346 
347 
348  !----------------------------------------------------------------------!
349  ! Synchronise Ip, B0, R0 in different CPOs !
350  !----------------------------------------------------------------------!
351 
352  coreprof_out(1)%globalparam%current_tot = equilibrium_in(1)%global_param%i_plasma
353  coreprof_out(1)%toroid_field%r0 = equilibrium_in(1)%global_param%toroid_field%r0
354  coreprof_out(1)%toroid_field%b0 = equilibrium_in(1)%global_param%toroid_field%b0
355  corefast_out(1)%toroid_field%r0 = equilibrium_in(1)%global_param%toroid_field%r0
356  corefast_out(1)%toroid_field%b0 = equilibrium_in(1)%global_param%toroid_field%b0
357  toroidfield_out(1)%current%value = equilibrium_in(1)%global_param%i_plasma
358  toroidfield_out(1)%r0 = equilibrium_in(1)%global_param%toroid_field%r0
359  toroidfield_out(1)%bvac_r%value = equilibrium_in(1)%global_param%toroid_field%b0
360 
361  RETURN
362 
363  END SUBROUTINE etsstart
364 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
365 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
366 
367 
368 
369 
370 END MODULE ets_start
subroutine allocate_coreimpur_cpo(NSLICE, NRHO, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP, COREIMPUR)
This routine allocates COREIMPUR CPO.
Definition: solver.f90:1
subroutine allocate_coreprof_cpo(NSLICE, NRHO, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP, COREPROF)
This routine allocates COREPROF CPO.
subroutine get_comp_dimensions(COMPOSITIONS, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP)
subroutine allocate_corefast_cpo(NSLICE, NRHO, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP, COREFAST)
This routine allocates COREFAST CPO.
This module contains routines for allocation/deallocation if CPOs used in ETS.
subroutine allocate_coresource_cpo(NSLICE, NRHO, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP, CORESOURCE)
This routine allocates CORESOURCE CPO.
subroutine allocate_neoclassic_cpo(NSLICE, NRHO, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP, NEOCLASSIC)
This routine allocates NEOCLASSIC CPO.
subroutine etsstart
Definition: ets_start.f90:9
subroutine allocate_coreneutrals_cpo(NSLICE, NRHO, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP, CORENEUTRALS)
subroutine allocate_toroidfield_cpo(NSLICE, TOROIDFIELD)
This routine allocates TOROIDFIELD CPO.
subroutine allocate_coretransp_cpo(NSLICE, NRHO, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP, CORETRANSP)
This routine allocates CORETRANSP CPO.