ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
fc2k_ets_start.f90
Go to the documentation of this file.
1 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
2 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
3  SUBROUTINE fc2k_etsstart &
4 !PARAMETERS & CPOs_IN:
5  (solver, equilibrium_in, coreprof_in, &
6 !CPOs_OUT:
7  coreprof_out, coretransp_out, coresource_out, &
8  coreimpur_out, corefast_out, &
9  coreneutrals_out, neoclassic_out, &
10  equilibrium_out, toroidfield_out, &
11 !BOUNDARY_CONDITIONS:
12  bc_main_int, bc_main_real, &
13  bc_imp_int, bc_imp_real, &
14  bc_neutr_int, bc_neutr_n0, bc_neutr_t0, &
15 !SPACE_RESOLUTION:
16  resolutions )
17 
18 !-------------------------------------------------------!
19 ! This routine generates the RHO grid for ETS !
20 ! and defines the number of ion species and saves !
21 ! it in COREPROF CPO. !
22 !-------------------------------------------------------!
23 ! Source: --- !
24 ! Developers: D.Kalupin !
25 ! Kontacts: D.Kalupin@fz-juelich.de !
26 ! !
27 ! Comments: --- !
28 ! !
29 !-------------------------------------------------------!
30 
31 
32 ! +++ Declaration of variables:
34  USE euitm_schemas
35  USE itm_types
36  USE copy_structures
37  USE ets_start
38 
39 
40  IMPLICIT NONE
41 
42 
43 ! +++ CPO derived types:
44  TYPE (type_coreprof), POINTER :: coreprof_in(:)
45  TYPE (type_equilibrium), POINTER :: equilibrium_in(:)
46 
47  TYPE (type_coreprof), POINTER :: coreprof_out(:)
48  TYPE (type_coretransp), POINTER :: coretransp_out(:)
49  TYPE (type_coresource), POINTER :: coresource_out(:)
50  TYPE (type_coreimpur), POINTER :: coreimpur_out(:)
51  TYPE (type_corefast), POINTER :: corefast_out(:)
52  TYPE (type_coreneutrals),POINTER :: coreneutrals_out(:)
53  TYPE (type_equilibrium), POINTER :: equilibrium_out(:)
54  TYPE (type_toroidfield), POINTER :: toroidfield_out(:)
55  TYPE (type_compositionc),POINTER :: compositionc_out(:)
56  TYPE (type_neoclassic), POINTER :: neoclassic_out(:)
57 
58 ! +++ General settings:
59  INTEGER :: solver
60 
61 ! +++ Boundary conditions:
62  INTEGER :: bc_main_int(12)
63  REAL (R8) :: bc_main_real(36)
64 
65  INTEGER :: bc_imp_int
66  REAL (R8) :: bc_imp_real(500)
67 
68  INTEGER :: bc_neutr_int(2)
69  REAL (R8) :: bc_neutr_n0(520)
70  REAL (R8) :: bc_neutr_t0(520)
71 
72 ! +++ Dimensions:
73  INTEGER :: resolutions(5)
74 
75 
76  INTEGER :: nrho, irho
77  INTEGER :: nnucl, inucl !number of nuclei species
78  INTEGER :: nion, iion !number of ion species
79  INTEGER :: nimp, iimp !number of impurity species
80  INTEGER, ALLOCATABLE :: nzimp(:) !number of ionization states for each impurity
81  INTEGER :: izimp
82  INTEGER :: nneut, ineut !number of neutrals species
83  INTEGER, ALLOCATABLE :: ncomp(:) !number of components for each neutral
84  INTEGER :: icomp
85  INTEGER, ALLOCATABLE :: ntype(:) !number of types for each neutral
86  INTEGER :: itype
87  INTEGER :: npsi !number of points for equilibrium 1-D arrays
88  INTEGER :: ndim1 !number of points for equilibrium 2-D arrays, first dimension
89  INTEGER :: ndim2 !number of points for equilibrium 2-D arrays, second dimension
90  INTEGER :: npoints !number of points for equilibrium boundary
91 
92 
93 ! +++ Local:
94  INTEGER :: psi_bnd_type
95  REAL (R8) :: psi_bnd_value(3)
96  INTEGER :: te_bnd_type
97  REAL (R8) :: te_bnd_value(3)
98  INTEGER :: ne_bnd_type
99  REAL (R8) :: ne_bnd_value(3)
100  INTEGER, ALLOCATABLE :: ni_bnd_type(:)
101  REAL (R8), ALLOCATABLE :: ni_bnd_value(:,:)
102  INTEGER, ALLOCATABLE :: ti_bnd_type(:)
103  REAL (R8), ALLOCATABLE :: ti_bnd_value(:,:)
104  INTEGER, ALLOCATABLE :: vtor_bnd_type(:)
105  REAL (R8), ALLOCATABLE :: vtor_bnd_value(:,:)
106 
107  INTEGER, ALLOCATABLE :: imp_bnd_type(:,:)
108  REAL (R8), ALLOCATABLE :: imp_bnd_value(:,:,:)
109 
110  INTEGER, ALLOCATABLE :: n0_bnd_type(:,:)
111  REAL (R8), ALLOCATABLE :: n0_bnd_value(:,:,:)
112  INTEGER, ALLOCATABLE :: t0_bnd_type(:,:)
113  REAL (R8), ALLOCATABLE :: t0_bnd_value(:,:,:)
114 
115 
116  INTEGER, PARAMETER :: nslice = 1
117  INTEGER :: i, neut_flag
118 
119 
120  !----------------------------------------------------------------------!
121  ! Fill input parameters !
122  !----------------------------------------------------------------------!
123  nrho = resolutions(1)
124  npsi = resolutions(2)
125  ndim1 = resolutions(3)
126  ndim2 = resolutions(4)
127  npoints = resolutions(5)
128 
129  CALL get_comp_dimensions(coreprof_in(1)%COMPOSITIONS, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp)
130 
131  IF (nion.GT.3) WRITE(*,*)'WARNING "NION > 3": approximations will be applied'
132  IF (nimp.GT.5) WRITE(*,*)'WARNING "NIMP > 5": approximations will be applied'
133 
134 
135 
136  !----------------------------------------------------------------------!
137  ! Set up boundary condition type and value for main plasma !
138  !----------------------------------------------------------------------!
139 
140  ALLOCATE (ni_bnd_type(nion))
141  ALLOCATE (ti_bnd_type(nion))
142  ALLOCATE (vtor_bnd_type(nion))
143 
144  ALLOCATE (ni_bnd_value(3,nion))
145  ALLOCATE (ti_bnd_value(3,nion))
146  ALLOCATE (vtor_bnd_value(3,nion))
147 
148 
149  psi_bnd_type = bc_main_int(1)
150  te_bnd_type = bc_main_int(2)
151  ne_bnd_type = bc_main_int(3)
152 
153  DO iion = 1,nion
154  ti_bnd_type(iion) = bc_main_int(4 +min(iion-1,2))
155  ni_bnd_type(iion) = bc_main_int(7 +min(iion-1,2))
156  vtor_bnd_type(iion) = bc_main_int(10+min(iion-1,2))
157  END DO
158 
159  DO i = 1,3
160  psi_bnd_value(i) = bc_main_real((i-1)*12+1)
161  te_bnd_value(i) = bc_main_real((i-1)*12+2)
162  ne_bnd_value(i) = bc_main_real((i-1)*12+6)
163  DO iion = 1,nion
164  ti_bnd_value(i,iion) = bc_main_real((i-1)*12+3 +min(iion-1,2))
165  ni_bnd_value(i,iion) = bc_main_real((i-1)*12+7 +min(iion-1,2))
166  vtor_bnd_value(i,iion) = bc_main_real((i-1)*12+10+min(iion-1,2))
167  END DO
168  END DO
169 
170 
171 
172 
173  !----------------------------------------------------------------------!
174  ! Set up boundary condition type and value for impurities !
175  !----------------------------------------------------------------------!
176  IF (nimp.GE.1) THEN
177  ALLOCATE (imp_bnd_value(nimp,3,maxval(nzimp)))
178  ALLOCATE (imp_bnd_type(nimp, maxval(nzimp)))
179 
180  DO iimp = 1,nimp
181  imp_bnd_type(iimp,:) = bc_imp_int
182  DO izimp = 1,nzimp(iimp)
183  imp_bnd_value(iimp,1,izimp) = bc_imp_real(min(4,(iimp-1))*100+izimp)
184  imp_bnd_value(iimp,2,izimp) = 0.0_r8
185  imp_bnd_value(iimp,3,izimp) = 0.0_r8
186  END DO
187  END DO
188  END IF
189 
190 
191 
192 
193 
194  !----------------------------------------------------------------------!
195  ! Set up boundary condition type and value for neutrals !
196  !----------------------------------------------------------------------!
197  IF (nneut.GE.1) THEN
198  ALLOCATE (n0_bnd_value(nneut,3,maxval(ntype)))
199  ALLOCATE (t0_bnd_value(nneut,3,maxval(ntype)))
200  ALLOCATE (n0_bnd_type(nneut, maxval(ntype)))
201  ALLOCATE (t0_bnd_type(nneut, maxval(ntype)))
202 
203  DO ineut = 1, nneut
204  DO itype = 1, ntype(ineut)
205  neut_flag = coreprof_in(1)%COMPOSITIONS%NEUTRALSCOMP(ineut)%TYPE(itype)%flag
206 
207  n0_bnd_type(ineut,itype) = bc_neutr_int(1)
208  t0_bnd_type(ineut,itype) = bc_neutr_int(2)
209 
210  n0_bnd_value(ineut,1,itype) = bc_neutr_n0(ineut+neut_flag*130)
211  t0_bnd_value(ineut,1,itype) = bc_neutr_t0(ineut+neut_flag*130)
212 
213  n0_bnd_value(ineut,2,itype) = 0._r8
214  t0_bnd_value(ineut,2,itype) = 0._r8
215  n0_bnd_value(ineut,3,itype) = 0._r8
216  t0_bnd_value(ineut,3,itype) = 0._r8
217  END DO
218  END DO
219  END IF
220 
221 
222 
223 
224  !----------------------------------------------------------------------!
225  ! Call CPO allocation !
226  !----------------------------------------------------------------------!
227  CALL etsstart &
228 !PARAMETERS & CPOs_IN:
229  (solver, equilibrium_in, coreprof_in, &
230 !CPOs_OUT:
231  coreprof_out, coretransp_out, coresource_out, &
232  coreimpur_out, corefast_out, &
233  coreneutrals_out, neoclassic_out, &
234  equilibrium_out, toroidfield_out, &
235 !BOUNDARY_CONDITIONS:
236  psi_bnd_type, ne_bnd_type, ni_bnd_type, &
237  ti_bnd_type, te_bnd_type, vtor_bnd_type, &
238  imp_bnd_type, n0_bnd_type, t0_bnd_type, &
239 !
240  psi_bnd_value, ne_bnd_value, ni_bnd_value, &
241  ti_bnd_value, te_bnd_value, vtor_bnd_value, &
242  imp_bnd_value, n0_bnd_value, t0_bnd_value, &
243 !SPACE_RESOLUTION:
244  nrho, npsi, ndim1, ndim2, npoints)
245 
246 
247 
248 
249  !----------------------------------------------------------------------!
250  ! Deallocate internal variables !
251  !----------------------------------------------------------------------!
252  IF (ALLOCATED(ni_bnd_type)) DEALLOCATE (ni_bnd_type)
253  IF (ALLOCATED(ti_bnd_type)) DEALLOCATE (ti_bnd_type)
254  IF (ALLOCATED(vtor_bnd_type)) DEALLOCATE (vtor_bnd_type)
255  IF (ALLOCATED(ni_bnd_value)) DEALLOCATE (ni_bnd_value)
256  IF (ALLOCATED(ti_bnd_value)) DEALLOCATE (ti_bnd_value)
257  IF (ALLOCATED(vtor_bnd_value))DEALLOCATE (vtor_bnd_value)
258  IF (ALLOCATED(imp_bnd_value)) DEALLOCATE (imp_bnd_value)
259  IF (ALLOCATED(n0_bnd_value)) DEALLOCATE (n0_bnd_value)
260  IF (ALLOCATED(t0_bnd_value)) DEALLOCATE (t0_bnd_value)
261  IF (ALLOCATED(n0_bnd_type)) DEALLOCATE (n0_bnd_type)
262  IF (ALLOCATED(t0_bnd_type)) DEALLOCATE (t0_bnd_type)
263  IF (ALLOCATED(nzimp)) DEALLOCATE (nzimp)
264  IF (ALLOCATED(ntype)) DEALLOCATE (ntype)
265  IF (ALLOCATED(ncomp)) DEALLOCATE (ncomp)
266 
267 
268 
269 
270  RETURN
271 
272 
273  END SUBROUTINE fc2k_etsstart
274 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
275 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
276 
277 
278 
279 
280 
281 
282 
Definition: solver.f90:1
subroutine get_comp_dimensions(COMPOSITIONS, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP)
This module contains routines for allocation/deallocation if CPOs used in ETS.
subroutine fc2k_etsstart
subroutine etsstart
Definition: ets_start.f90:9