11 (
solver, equilibrium_in, coreprof_in, &
13 coreprof_out, coretransp_out, coresource_out, &
14 coreimpur_out, corefast_out, &
15 coreneutrals_out, neoclassic_out, &
16 equilibrium_out, toroidfield_out, &
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, &
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, &
26 nrho, npsi, ndim1, ndim2, npoints)
47 USE deallocate_structures
54 TYPE (type_coreprof
),
POINTER :: coreprof_in(:)
55 TYPE (type_equilibrium
),
POINTER :: equilibrium_in(:)
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(:)
66 TYPE (type_neoclassic
),
POINTER :: neoclassic_out(:)
75 INTEGER :: nnucl, inucl
78 INTEGER,
ALLOCATABLE :: nzimp(:)
80 INTEGER :: nneut, ineut
81 INTEGER,
ALLOCATABLE :: ncomp(:)
83 INTEGER,
ALLOCATABLE :: ntype(:)
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(:,:)
105 INTEGER,
ALLOCATABLE :: imp_bnd_type(:,:)
106 REAL (R8),
ALLOCATABLE :: imp_bnd_value(:,:,:)
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(:,:,:)
113 REAL (R8),
ALLOCATABLE :: rho(:)
114 REAL (R8),
ALLOCATABLE :: rhon(:)
117 INTEGER,
PARAMETER :: nslice = 1
118 INTEGER :: i, neut_flag
127 CALL
get_comp_dimensions(coreprof_in(1)%COMPOSITIONS, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp)
129 CALL
allocate_coreprof_cpo(nslice, nrho, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, coreprof_out )
131 CALL
allocate_corefast_cpo(nslice, nrho, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, corefast_out )
137 ALLOCATE (equilibrium_out(1))
138 CALL copy_cpo(equilibrium_in(1), equilibrium_out(1))
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
157 ALLOCATE (rhon(nrho))
159 rhob = equilibrium_in(1)%profiles_1d%rho_tor(
SIZE(equilibrium_in(1)%profiles_1d%rho_tor))
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
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
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
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)
205 CALL deallocate_cpo(coreneutrals_out(1)%COMPOSITIONS)
206 CALL copy_cpo(coreprof_in(1)%COMPOSITIONS, coreneutrals_out(1)%COMPOSITIONS)
209 CALL deallocate_cpo(coreimpur_out(1)%COMPOSITIONS)
210 CALL copy_cpo(coreprof_in(1)%COMPOSITIONS, coreimpur_out(1)%COMPOSITIONS)
212 CALL deallocate_cpo(neoclassic_out(1)%COMPOSITIONS)
213 CALL copy_cpo(coreprof_in(1)%COMPOSITIONS, neoclassic_out(1)%COMPOSITIONS)
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
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
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
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
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
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
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
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
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
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
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)
317 DEALLOCATE(imp_bnd_type, imp_bnd_value)
320 DEALLOCATE(ni_bnd_type, ti_bnd_type, vtor_bnd_type)
321 DEALLOCATE(ni_bnd_value, ti_bnd_value, vtor_bnd_value)
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
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
342 DEALLOCATE(n0_bnd_type, t0_bnd_type, n0_bnd_value, t0_bnd_value)
345 DEALLOCATE(rho, rhon)
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
subroutine allocate_coreimpur_cpo(NSLICE, NRHO, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP, COREIMPUR)
This routine allocates COREIMPUR CPO.
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 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.