ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
convert_neutrals.f90
Go to the documentation of this file.
1 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
2 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
9 
10  CONTAINS
11 
12 
13 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
14 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
15 
22  (equilibrium, coreprof, control_integer, control_double, &
23  geometry, profiles, control)
24 
25 !-------------------------------------------------------!
26 ! This routine converts CPOs into NEUTRALS !
27 ! derived types. !
28 !-------------------------------------------------------!
29 ! Source: --- !
30 ! Developers: D.Kalupin !
31 ! Kontacts: D.Kalupin@fz-juelich.de !
32 ! !
33 ! Comments: --- !
34 ! !
35 !-------------------------------------------------------!
36 
37 
38  USE euitm_schemas
39 
40  USE ets_plasma
41 
42  IMPLICIT NONE
43 
44 ! +++ CPO derived types:
45  TYPE (type_equilibrium), POINTER :: equilibrium(:)
46  TYPE (type_coreprof), POINTER :: coreprof(:)
47  INTEGER, INTENT(IN) :: control_integer(2) !integer control parameters
48  REAL (R8), INTENT(IN) :: control_double(5) !real control parameters
49 
50 ! +++ NEUTRALS derived types:
51  TYPE (magnetic_geometry), INTENT(INOUT) :: geometry !contains all geometry quantities
52  TYPE (plasma_profiles), INTENT(INOUT) :: profiles !contains profiles of plasma parameters
53  TYPE (run_control), INTENT(INOUT) :: control !contains all parameters required by run
54 
55  INTEGER :: nrho, neq
56 
57  nrho = SIZE(coreprof(1)%rho_tor)
58  neq = SIZE(equilibrium(1)%profiles_1d%rho_tor)
59 
60 
61 ! +++ Convert geometry:
62  geometry%RHO = coreprof(1)%rho_tor
63 
64  CALL l3deriv(equilibrium(1)%profiles_1d%volume, equilibrium(1)%profiles_1d%rho_tor, neq, &
65  geometry%VPR, geometry%RHO, nrho)
66 
67 
68 ! +++ Convert profiles:
69  profiles%ZION = coreprof(1)%composition%zion
70  profiles%MION = coreprof(1)%composition%amn
71 
72  profiles%NI = coreprof(1)%ni%value
73  profiles%NE = coreprof(1)%ne%value
74  profiles%TI = coreprof(1)%ti%value
75  profiles%TE = coreprof(1)%te%value
76 
77 ! +++ Convert control parameters:
78  control%SOLVER_TYPE = control_integer(1)
79  control%SIGMA_SOURCE = control_integer(2)
80  control%TAU = control_double(1)
81  control%AMIX = control_double(2)
82  control%AMIXTR = control_double(3)
83  control%CONV = control_double(4)
84  control%CONVREC = control_double(5)
85 
86 
87  RETURN
88 
89 
90  END SUBROUTINE convert_cpo_to_neutrals_types
91 
92 
93 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
94 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
95 
96 
97 
98 
99 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
100 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
101 
108  (sources, coresource)
109 
110 !-------------------------------------------------------!
111 ! This routine converts NEUTRALS into the CPO !
112 ! derived types. !
113 !-------------------------------------------------------!
114 ! Source: --- !
115 ! Developers: D.Kalupin !
116 ! Kontacts: D.Kalupin@fz-juelich.de !
117 ! !
118 ! Comments: --- !
119 ! !
120 !-------------------------------------------------------!
121 
122 
123  USE euitm_schemas
124 
125  USE ets_plasma
126 
127  IMPLICIT NONE
128 
129 ! +++ CPO derived types:
130  TYPE (type_coresource), POINTER :: coresource(:) !input CPO with sources
131 
132 ! +++ NEUTRALS derived types:
133  TYPE (sources_and_sinks) :: sources !contains profiles of sources
134 
135 
136 ! +++ Convert profiles of sources:
137  coresource(1)%VALUES(1)%qe%exp = sources%QE_EXP
138  coresource(1)%VALUES(1)%si%exp = sources%SI_EXP
139  coresource(1)%VALUES(1)%qi%exp = sources%QI_EXP
140 
141 
142 
143  RETURN
144 
145 
146  END SUBROUTINE convert_neutrals_to_cpo_types
147 
148 
149 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
150 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
151 
152 
153 
154  END MODULE convert_neutrals
subroutine l3deriv(y_in, x_in, nr_in, dydx_out, x_out, nr_out)
Definition: l3interp.f90:59
subroutine profiles(p0, rbphi, dp0, drbphi, a)
Definition: profiles.f90:1
subroutine convert_cpo_to_neutrals_types(EQUILIBRIUM, COREPROF, CONTROL_INTEGER, CONTROL_DOUBLE, GEOMETRY, PROFILES, CONTROL)
??
The module declares types of variables used in ETS (transport code)
Definition: ets_plasma.f90:8
subroutine convert_neutrals_to_cpo_types(SOURCES, CORESOURCE)
??