5 (
solver, equilibrium_in, coreprof_in, &
7 coreprof_out, coretransp_out, coresource_out, &
8 coreimpur_out, corefast_out, &
9 coreneutrals_out, neoclassic_out, &
10 equilibrium_out, toroidfield_out, &
12 bc_main_int, bc_main_real, &
13 bc_imp_int, bc_imp_real, &
14 bc_neutr_int, bc_neutr_n0, bc_neutr_t0, &
44 TYPE (type_coreprof
),
POINTER :: coreprof_in(:)
45 TYPE (type_equilibrium
),
POINTER :: equilibrium_in(:)
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(:)
62 integer,
intent(in),
dimension(:) :: bc_main_int
63 real(R8),
intent(in),
dimension(:) :: bc_main_real
68 REAL (R8) :: bc_imp_real(500)
70 INTEGER :: bc_neutr_int(2)
71 REAL (R8) :: bc_neutr_n0(520)
72 REAL (R8) :: bc_neutr_t0(520)
75 INTEGER :: resolutions(5)
79 INTEGER :: nnucl, inucl
82 INTEGER,
ALLOCATABLE :: nzimp(:)
84 INTEGER :: nneut, ineut
85 INTEGER,
ALLOCATABLE :: ncomp(:)
87 INTEGER,
ALLOCATABLE :: ntype(:)
96 INTEGER :: psi_bnd_type
97 REAL (R8) :: psi_bnd_value(3)
98 INTEGER :: te_bnd_type
99 REAL (R8) :: te_bnd_value(3)
100 INTEGER :: ne_bnd_type
101 REAL (R8) :: ne_bnd_value(3)
102 INTEGER,
ALLOCATABLE :: ni_bnd_type(:)
103 REAL (R8),
ALLOCATABLE :: ni_bnd_value(:,:)
104 INTEGER,
ALLOCATABLE :: ti_bnd_type(:)
105 REAL (R8),
ALLOCATABLE :: ti_bnd_value(:,:)
106 INTEGER,
ALLOCATABLE :: vtor_bnd_type(:)
107 REAL (R8),
ALLOCATABLE :: vtor_bnd_value(:,:)
109 INTEGER,
ALLOCATABLE :: imp_bnd_type(:,:)
110 REAL (R8),
ALLOCATABLE :: imp_bnd_value(:,:,:)
112 INTEGER,
ALLOCATABLE :: n0_bnd_type(:,:)
113 REAL (R8),
ALLOCATABLE :: n0_bnd_value(:,:,:)
114 INTEGER,
ALLOCATABLE :: t0_bnd_type(:,:)
115 REAL (R8),
ALLOCATABLE :: t0_bnd_value(:,:,:)
118 INTEGER,
PARAMETER :: nslice = 1
119 INTEGER :: i, neut_flag
120 integer,
parameter :: nion_max=7
126 nrho = resolutions(1)
127 npsi = resolutions(2)
128 ndim1 = resolutions(3)
129 ndim2 = resolutions(4)
130 npoints = resolutions(5)
132 CALL
get_comp_dimensions(coreprof_in(1)%COMPOSITIONS, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp)
135 IF (nimp.GT.5)
WRITE(*,*)
'WARNING "NIMP > 5": approximations will be applied'
143 ALLOCATE (ni_bnd_type(nion))
144 ALLOCATE (ti_bnd_type(nion))
145 ALLOCATE (vtor_bnd_type(nion))
147 ALLOCATE (ni_bnd_value(3,nion))
148 ALLOCATE (ti_bnd_value(3,nion))
149 ALLOCATE (vtor_bnd_value(3,nion))
152 psi_bnd_type = bc_main_int(1)
153 te_bnd_type = bc_main_int(2)
154 ne_bnd_type = bc_main_int(3)
157 ti_bnd_type(iion) = bc_main_int(4 +iion-1)
158 ni_bnd_type(iion) = bc_main_int(4 +nion_max+iion-1)
159 vtor_bnd_type(iion) = bc_main_int(4+2*nion_max+iion-1)
163 psi_bnd_value(i) = bc_main_real((i-1)*nion_max*3+1)
164 te_bnd_value(i) = bc_main_real((i-1)*nion_max*3+2)
165 ne_bnd_value(i) = bc_main_real((i-1)*nion_max*3+3)
167 ti_bnd_value(i,iion) = bc_main_real((i-1)*nion_max*3+4+iion-1)
168 ni_bnd_value(i,iion) = bc_main_real((i-1)*nion_max*3+4+nion_max+iion-1)
169 vtor_bnd_value(i,iion) = bc_main_real((i-1)*nion_max*3+4+2*nion_max+iion-1)
180 ALLOCATE (imp_bnd_value(nimp,3,maxval(nzimp)))
181 ALLOCATE (imp_bnd_type(nimp, maxval(nzimp)))
184 imp_bnd_type(iimp,:) = bc_imp_int
185 DO izimp = 1,nzimp(iimp)
186 imp_bnd_value(iimp,1,izimp) = bc_imp_real(min(4,(iimp-1))*100+izimp)
187 imp_bnd_value(iimp,2,izimp) = 0.0_r8
188 imp_bnd_value(iimp,3,izimp) = 0.0_r8
201 ALLOCATE (n0_bnd_value(nneut,3,maxval(ntype)))
202 ALLOCATE (t0_bnd_value(nneut,3,maxval(ntype)))
203 ALLOCATE (n0_bnd_type(nneut, maxval(ntype)))
204 ALLOCATE (t0_bnd_type(nneut, maxval(ntype)))
207 DO itype = 1, ntype(ineut)
208 neut_flag = coreprof_in(1)%COMPOSITIONS%NEUTRALSCOMP(ineut)%TYPE(itype)%flag
210 n0_bnd_type(ineut,itype) = bc_neutr_int(1)
211 t0_bnd_type(ineut,itype) = bc_neutr_int(2)
213 n0_bnd_value(ineut,1,itype) = bc_neutr_n0(ineut+neut_flag*130)
214 t0_bnd_value(ineut,1,itype) = bc_neutr_t0(ineut+neut_flag*130)
216 n0_bnd_value(ineut,2,itype) = 0._r8
217 t0_bnd_value(ineut,2,itype) = 0._r8
218 n0_bnd_value(ineut,3,itype) = 0._r8
219 t0_bnd_value(ineut,3,itype) = 0._r8
232 (
solver, equilibrium_in, coreprof_in, &
234 coreprof_out, coretransp_out, coresource_out, &
235 coreimpur_out, corefast_out, &
236 coreneutrals_out, neoclassic_out, &
237 equilibrium_out, toroidfield_out, &
239 psi_bnd_type, ne_bnd_type, ni_bnd_type, &
240 ti_bnd_type, te_bnd_type, vtor_bnd_type, &
241 imp_bnd_type, n0_bnd_type, t0_bnd_type, &
243 psi_bnd_value, ne_bnd_value, ni_bnd_value, &
244 ti_bnd_value, te_bnd_value, vtor_bnd_value, &
245 imp_bnd_value, n0_bnd_value, t0_bnd_value, &
247 nrho, npsi, ndim1, ndim2, npoints)
255 IF (
ALLOCATED(ni_bnd_type))
DEALLOCATE (ni_bnd_type)
256 IF (
ALLOCATED(ti_bnd_type))
DEALLOCATE (ti_bnd_type)
257 IF (
ALLOCATED(vtor_bnd_type))
DEALLOCATE (vtor_bnd_type)
258 IF (
ALLOCATED(ni_bnd_value))
DEALLOCATE (ni_bnd_value)
259 IF (
ALLOCATED(ti_bnd_value))
DEALLOCATE (ti_bnd_value)
260 IF (
ALLOCATED(vtor_bnd_value))
DEALLOCATE (vtor_bnd_value)
261 IF (
ALLOCATED(imp_bnd_value))
DEALLOCATE (imp_bnd_value)
262 IF (
ALLOCATED(n0_bnd_value))
DEALLOCATE (n0_bnd_value)
263 IF (
ALLOCATED(t0_bnd_value))
DEALLOCATE (t0_bnd_value)
264 IF (
ALLOCATED(n0_bnd_type))
DEALLOCATE (n0_bnd_type)
265 IF (
ALLOCATED(t0_bnd_type))
DEALLOCATE (t0_bnd_type)
266 IF (
ALLOCATED(nzimp))
DEALLOCATE (nzimp)
267 IF (
ALLOCATED(ntype))
DEALLOCATE (ntype)
268 IF (
ALLOCATED(ncomp))
DEALLOCATE (ncomp)
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_etsstart2