ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
coredelta2coreprof.f90
Go to the documentation of this file.
1 
2 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
3 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
4 
5  !-------------------------------------------------------!
6  ! This routine adds values from coredelta CPO !
7  ! to a coreprof CPO !
8  !-------------------------------------------------------!
9  ! Delta: --- !
10  ! Developers: D.Kalupin !
11  ! Kontacts: Denis.Kalupin@efda.org !
12  ! !
13  ! Comments: created for ETS workflow !
14  ! !
15  !-------------------------------------------------------!
16 
17  SUBROUTINE coredelta2coreprof &
18  (coreprof_pivot, coredelta, coreprof_new)
19 
20  USE itm_constants
21  USE euitm_schemas
22  USE copy_structures
23  USE interpolate_cpo
24  USE deallocate_structures
26 
27 
28  IMPLICIT NONE
29 
30 
31 
32 ! +++ CPOs
33  TYPE (type_coreprof), POINTER :: coreprof_pivot(:)
34  TYPE (type_coreprof), POINTER :: coreprof_new(:)
35  TYPE (type_coredelta), POINTER :: coredelta_interp(:)
36  TYPE (type_coredelta), POINTER :: coredelta(:)
37  TYPE (type_coredelta), POINTER :: coredelta_v1(:)
38 
39  INTEGER :: nrho
40  INTEGER, PARAMETER :: nslice = 1
41  INTEGER :: nrho1, nrho2
42  INTEGER :: nnucl
43  INTEGER :: nion, iion
44  INTEGER :: nimp
45  INTEGER, ALLOCATABLE :: nzimp(:)
46  INTEGER :: nneut
47  INTEGER, ALLOCATABLE :: ncomp(:)
48  INTEGER, ALLOCATABLE :: ntype(:)
49 
50 
51 ! +++ Interpolate coredelta CPO to the grid of pivot coreprof CPO
52 
53  nrho = SIZE(coreprof_pivot(1)%rho_tor)
54  CALL get_comp_dimensions(coreprof_pivot(1)%COMPOSITIONS, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp)
55  CALL allocate_coredelta_cpo(nslice, nrho, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, coredelta_interp)
56  CALL copy_cpo(coreprof_pivot(1)%COMPOSITIONS, coredelta_interp(1)%COMPOSITIONS)
57  coredelta_interp(1)%VALUES(1)%rho_tor = coreprof_pivot(1)%rho_tor
58 
59 
60 
61  ALLOCATE (coredelta_v1(1))
62  ALLOCATE (coredelta_v1(1)%VALUES(1))
63  CALL copy_cpo(coredelta(1)%COMPOSITIONS, coredelta_v1(1)%COMPOSITIONS)
64  CALL copy_cpo(coredelta(1)%VALUES(1), coredelta_v1(1)%VALUES(1))
65 
66 
67  CALL interpolate_delta(coredelta_v1(1), coredelta_interp(1))
68 
69 
70 
71 ! +++ Allocate output CPO and internal derived types:
72  ALLOCATE (coreprof_new(1))
73  CALL copy_cpo(coreprof_pivot(1), coreprof_new(1))
74 
75 
76 
77 ! +++ Fill output CPO with data:
78  coreprof_new(1)%psi%value = coreprof_pivot(1)%psi%value + coredelta_interp(1)%VALUES(1)%delta_psi
79  coreprof_new(1)%te%value = coreprof_pivot(1)%te%value + coredelta_interp(1)%VALUES(1)%delta_te
80  coreprof_new(1)%ne%value = coreprof_pivot(1)%ne%value + coredelta_interp(1)%VALUES(1)%delta_ne
81  coreprof_new(1)%ti%value = coreprof_pivot(1)%ti%value + coredelta_interp(1)%VALUES(1)%delta_ti
82  coreprof_new(1)%ni%value = coreprof_pivot(1)%ni%value + coredelta_interp(1)%VALUES(1)%delta_ni
83  coreprof_new(1)%vtor%value = coreprof_pivot(1)%vtor%value + coredelta_interp(1)%VALUES(1)%delta_vtor
84 
85 
86  CALL deallocate_cpo(coredelta_interp)
87  CALL deallocate_cpo(coredelta_v1)
88 
89 
90  RETURN
91 
92 
93  END SUBROUTINE coredelta2coreprof
94 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
95 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
96 
subroutine allocate_coredelta_cpo(NSLICE, NRHO, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP, COREDELTA)
This routine allocates COREDELTA CPO.
subroutine get_comp_dimensions(COMPOSITIONS, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP)
subroutine coredelta2coreprof(COREPROF_PIVOT, COREDELTA, COREPROF_NEW)
subroutine interpolate_delta(COREDELTA_IN, COREDELTA_OUT)
This module contains routines for allocation/deallocation if CPOs used in ETS.