ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
ignore_impurity.f90
Go to the documentation of this file.
1 !-------------------------------------------------------!
2 !-------------------------------------------------------!
3 
4  SUBROUTINE ignore_impurity (COREPROF, COREIMPUR)
5 
6 !-------------------------------------------------------!
7 ! This routine is used by the ETS workflow !
8 ! in case when sources should be ignored !
9 !-------------------------------------------------------!
10 ! Source: --- !
11 ! Developers: D.Kalupin !
12 ! Kontacts: Denis.Kalupin@efda.org !
13 ! !
14 ! Comments: output COREIMPUR CPO is !
15 ! allocated inside the module !
16 ! !
17 !-------------------------------------------------------!
18 
19 
20  USE euitm_schemas
21  USE euitm_routines
23  USE itm_types
24  USE copy_structures
25  USE deallocate_structures
26 
27  IMPLICIT NONE
28 
29 
30  INTEGER :: ifail
31 
32 
33 ! +++ CPO derived types:
34  TYPE (type_coreprof), POINTER :: coreprof(:) !input CPO with internal ETS parameters profiles from previous time
35  TYPE (type_coreimpur), POINTER :: coreimpur(:) !output CPO with sources
36 
37 
38 ! +++ Dimensions:
39  INTEGER, PARAMETER :: nslice = 1 !number of CPO ocurancies in the work flow
40  INTEGER :: nrho !number of radial points (input, determined from COREPROF CPO)
41  INTEGER :: nion !number of ion species (input, determined from COREPROF CPO)
42  INTEGER :: nimp !number of impurities (input)
43  INTEGER :: nnucl !number of nuclei species
44  INTEGER, ALLOCATABLE :: nzimp(:) !number of ionization states for each impurity
45  INTEGER :: nneut !number of neutrals species
46  INTEGER, ALLOCATABLE :: ncomp(:) !number of components for each neutral
47  INTEGER, ALLOCATABLE :: ntype(:) !number of types for each neutral
48 
49 
50 
51 ! +++ Set dimensions:
52  nrho = SIZE (coreprof(1)%rho_tor, dim=1)
53  CALL get_comp_dimensions(coreprof(1)%COMPOSITIONS, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp)
54 
55 
56 ! +++ Allocate output CPO:
57  CALL allocate_coreimpur_cpo(nslice, nrho, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, coreimpur)
58  CALL deallocate_cpo(coreimpur(1)%COMPOSITIONS)
59  CALL copy_cpo(coreprof(1)%COMPOSITIONS, coreimpur(1)%COMPOSITIONS)
60 
61 
62 ! +++ Save output in CPO:
63  coreimpur(1)%time = coreprof(1)%time !time [s]
64 
65  coreimpur(1)%rho_tor = coreprof(1)%rho_tor !rho [m]
66  coreimpur(1)%rho_tor_norm = coreprof(1)%rho_tor/coreprof(1)%rho_tor(nrho) !rho [m]
67 
68 ! +++ Deallocation of internal variables:
69  IF(ALLOCATED(nzimp)) DEALLOCATE ( nzimp )
70  IF(ALLOCATED(ncomp)) DEALLOCATE ( ncomp )
71  IF(ALLOCATED(ntype)) DEALLOCATE ( ntype )
72 
73 
74  RETURN
75 
76 
77  END SUBROUTINE ignore_impurity
78 
79 !-------------------------------------------------------!
80 !-------------------------------------------------------!
subroutine allocate_coreimpur_cpo(NSLICE, NRHO, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP, COREIMPUR)
This routine allocates COREIMPUR CPO.
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 ignore_impurity(COREPROF, COREIMPUR)