ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
synchrotron.f90
Go to the documentation of this file.
1 MODULE synchrotron
2 
3 CONTAINS
4 
5 
6 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
7 ! + + + + + + + + + + + + SYNCHROTRON + + + + + + + + + +
8 
9  SUBROUTINE synchrotron_radiation(COREPROF, CORESOURCE)
10 
11 !-------------------------------------------------------!
12 ! This routine calculate sybchrotron radiation !
13 ! !
14 !-------------------------------------------------------!
15 ! Source: --- !
16 ! Developers: I.M.Ivanova-Stanik !
17 ! Kontacts: irena.ivanova-stanik@ifpilm.pl !
18 ! !
19 ! Comments: might change after the ITM !
20 ! data stucture is finalized !
21 ! !
22 !-------------------------------------------------------!
23 
24 
25  USE itm_types
26  USE itm_constants
27  USE euitm_schemas
28  USE copy_structures
30 
31 
32  IMPLICIT NONE
33 
34 ! +++ CPO derived types:
35  TYPE (type_coreprof), POINTER :: coreprof(:) !input CPO main plasma
36  TYPE (type_coresource), POINTER :: coresource(:) !output CPO with syncrhotron radiation
37 
38 
39 
40 ! +++ Dimensions:
41  INTEGER :: nrho !number of radial points (input, determined from COREPROF CPO)
42  INTEGER :: nnucl !number of ion species (input, determined from COREPROF CPO)
43  INTEGER :: nion !number of ion species (input, determined from COREPROF CPO)
44  INTEGER :: nimp !number of impurity species (input, determined from COREIMPUR CPO)
45  INTEGER :: nneut !number of neutrals species (input)
46  INTEGER, ALLOCATABLE :: ntype(:) !number of impurity ionization states (input)
47  INTEGER, ALLOCATABLE :: ncomp(:) !max_number of distinct atoms enter the composition-"1" wich is neutral
48  INTEGER, ALLOCATABLE :: nzimp(:)
49 
50  INTEGER, PARAMETER :: nocur = 1 !number of CPO ocurancies in the work flow
51 
52 
53 
54 ! +++ Set dimensions:
55  nrho = SIZE (coreprof(1)%rho_tor)
56  CALL get_comp_dimensions(coreprof(1)%COMPOSITIONS, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp)
57 
58 ! +++ Allocate output CPOs:
59  CALL allocate_coresource_cpo(nocur, nrho, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, coresource)
60  CALL copy_cpo(coreprof(1)%COMPOSITIONS, coresource(1)%COMPOSITIONS)
61 
62 
63  coresource(1)%datainfo%cocos = 13
64  coresource(1)%time = coreprof(1)%time
65  coresource(1)%VALUES(1)%rho_tor = coreprof(1)%rho_tor
66  coresource(1)%VALUES(1)%rho_tor_norm = coreprof(1)%rho_tor/coreprof(1)%rho_tor(nrho)
67 
68 
69 ! +++ Syncrhotron radiation
70  coresource(1)%VALUES(1)%qe%exp = 0.01_r8*6.2e-20_r8*coreprof(1)%toroid_field%B0**2.0*coreprof(1)%ne%value*coreprof(1)%te%value
71 
72 
73 ! +++ ADD IDENTIFIER TO OUTPUT CPO VALUES(1):
74  ALLOCATE (coresource%VALUES(1)%sourceid%id(1))
75  ALLOCATE (coresource(1)%VALUES(1)%sourceid%description(1))
76  coresource(1)%VALUES(1)%sourceid%id = 'syncrotronradiation'
77  coresource(1)%VALUES(1)%sourceid%flag = 17
78  coresource(1)%VALUES(1)%sourceid%description = 'Source from syncrotron radiation'
79 
80 
81  IF(ALLOCATED(ntype)) DEALLOCATE (ntype)
82  IF(ALLOCATED(ncomp)) DEALLOCATE (ncomp)
83  IF(ALLOCATED(nzimp)) DEALLOCATE (nzimp)
84 
85 
86 
87  RETURN
88 
89 
90  END SUBROUTINE synchrotron_radiation
91 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
92 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
93 
94 
95 
96 
97 END MODULE synchrotron
98 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
99 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
subroutine get_comp_dimensions(COMPOSITIONS, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP)
subroutine synchrotron_radiation(COREPROF, CORESOURCE)
Definition: synchrotron.f90:9
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.