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 :: bc_main_int(12)
63 REAL (R8) :: bc_main_real(36)
66 REAL (R8) :: bc_imp_real(500)
68 INTEGER :: bc_neutr_int(2)
69 REAL (R8) :: bc_neutr_n0(520)
70 REAL (R8) :: bc_neutr_t0(520)
73 INTEGER :: resolutions(5)
77 INTEGER :: nnucl, inucl
80 INTEGER,
ALLOCATABLE :: nzimp(:)
82 INTEGER :: nneut, ineut
83 INTEGER,
ALLOCATABLE :: ncomp(:)
85 INTEGER,
ALLOCATABLE :: ntype(:)
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(:,:)
107 INTEGER,
ALLOCATABLE :: imp_bnd_type(:,:)
108 REAL (R8),
ALLOCATABLE :: imp_bnd_value(:,:,:)
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(:,:,:)
116 INTEGER,
PARAMETER :: nslice = 1
117 INTEGER :: i, neut_flag
123 nrho = resolutions(1)
124 npsi = resolutions(2)
125 ndim1 = resolutions(3)
126 ndim2 = resolutions(4)
127 npoints = resolutions(5)
129 CALL
get_comp_dimensions(coreprof_in(1)%COMPOSITIONS, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp)
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'
140 ALLOCATE (ni_bnd_type(nion))
141 ALLOCATE (ti_bnd_type(nion))
142 ALLOCATE (vtor_bnd_type(nion))
144 ALLOCATE (ni_bnd_value(3,nion))
145 ALLOCATE (ti_bnd_value(3,nion))
146 ALLOCATE (vtor_bnd_value(3,nion))
149 psi_bnd_type = bc_main_int(1)
150 te_bnd_type = bc_main_int(2)
151 ne_bnd_type = bc_main_int(3)
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))
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)
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))
177 ALLOCATE (imp_bnd_value(nimp,3,maxval(nzimp)))
178 ALLOCATE (imp_bnd_type(nimp, maxval(nzimp)))
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
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)))
204 DO itype = 1, ntype(ineut)
205 neut_flag = coreprof_in(1)%COMPOSITIONS%NEUTRALSCOMP(ineut)%TYPE(itype)%flag
207 n0_bnd_type(ineut,itype) = bc_neutr_int(1)
208 t0_bnd_type(ineut,itype) = bc_neutr_int(2)
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)
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
229 (
solver, equilibrium_in, coreprof_in, &
231 coreprof_out, coretransp_out, coresource_out, &
232 coreimpur_out, corefast_out, &
233 coreneutrals_out, neoclassic_out, &
234 equilibrium_out, toroidfield_out, &
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, &
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, &
244 nrho, npsi, ndim1, ndim2, npoints)
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)
subroutine get_comp_dimensions(COMPOSITIONS, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP)
This module contains routines for allocation/deallocation if CPOs used in ETS.