ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
coreprof2coredelta.f90
Go to the documentation of this file.
1 
2 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
3 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
4 
5  !-------------------------------------------------------!
6  ! This routine converts two coreprof CPOs !
7  ! to a single coredelta CPO by taking !
8  ! difference between them !
9  !-------------------------------------------------------!
10  ! Delta: --- !
11  ! Developers: D.Kalupin !
12  ! Kontacts: Denis.Kalupin@efda.org !
13  ! !
14  ! Comments: created for ETS workflow !
15  ! !
16  !-------------------------------------------------------!
17 
18  SUBROUTINE coreprof2coredelta &
19  (coreprof_pivot, coreprof_new, coredelta)
20 
21  USE itm_constants
22  USE euitm_schemas
23  USE copy_structures
24  USE interpolate_cpo
26  USE deallocate_structures
27 
28 
29  IMPLICIT NONE
30 
31 
32 
33 ! +++ CPOs
34  TYPE (type_coreprof), POINTER :: coreprof_pivot(:)
35  TYPE (type_coreprof), POINTER :: coreprof_new(:)
36  TYPE (type_coreprof), POINTER :: coreprof_interp(:)
37  TYPE (type_coredelta), POINTER :: coredelta(:)
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 pivot CPO to the grid of new CPO
52  ALLOCATE (coreprof_interp(1))
53  CALL copy_cpo(coreprof_new(1), coreprof_interp(1))
54  CALL interpolate_prof(coreprof_pivot(1), coreprof_interp(1))
55  nrho = SIZE(coreprof_new(1)%rho_tor)
56 
57 
58 ! +++ Allocate output CPO and internal derived types:
59  CALL get_comp_dimensions(coreprof_new(1)%COMPOSITIONS, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp)
60  CALL allocate_coredelta_cpo(nslice, nrho, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, coredelta)
61  CALL copy_cpo(coreprof_new(1)%COMPOSITIONS, coredelta(1)%COMPOSITIONS)
62 
63 
64 ! +++ Fill output CPO with data:
65  coredelta(1)%VALUES(1)%rho_tor = coreprof_new(1)%rho_tor
66  coredelta(1)%VALUES(1)%rho_tor_norm = coreprof_new(1)%rho_tor_norm
67  coredelta(1)%VALUES(1)%psi = coreprof_new(1)%psi%value
68  coredelta(1)%VALUES(1)%delta_psi = coreprof_new(1)%psi%value - coreprof_interp(1)%psi%value
69  coredelta(1)%VALUES(1)%delta_te = coreprof_new(1)%te%value - coreprof_interp(1)%te%value
70  coredelta(1)%VALUES(1)%delta_ne = coreprof_new(1)%ne%value - coreprof_interp(1)%ne%value
71  coredelta(1)%VALUES(1)%delta_ti = coreprof_new(1)%ti%value - coreprof_interp(1)%ti%value
72  coredelta(1)%VALUES(1)%delta_ni = coreprof_new(1)%ni%value - coreprof_interp(1)%ni%value
73  coredelta(1)%VALUES(1)%delta_vtor = coreprof_new(1)%vtor%value - coreprof_interp(1)%vtor%value
74 
75 
76 ! +++ ADD IDENTIFIER TO OUTPUT CPO VALUES(1):
77  ALLOCATE (coredelta(1)%VALUES(1)%deltaid%id(1))
78  ALLOCATE (coredelta(1)%VALUES(1)%deltaid%description(1))
79  coredelta(1)%VALUES(1)%deltaid%id = 'unspecified'
80  coredelta(1)%VALUES(1)%deltaid%flag = 0
81  coredelta(1)%VALUES(1)%deltaid%description = 'Unspecified coredelta'
82 
83 
84 10 IF(ALLOCATED(nzimp)) DEALLOCATE (nzimp)
85  IF(ALLOCATED(ncomp)) DEALLOCATE (ncomp)
86  IF(ALLOCATED(ntype)) DEALLOCATE (ntype)
87 
88  CALL deallocate_cpo(coreprof_interp)
89 
90 
91  RETURN
92 
93 
94  END SUBROUTINE coreprof2coredelta
95 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
96 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
97 
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 interpolate_prof(COREPROF_IN, COREPROF_OUT)
This module contains routines for allocation/deallocation if CPOs used in ETS.
subroutine coreprof2coredelta(COREPROF_PIVOT, COREPROF_NEW, COREDELTA)