ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
fc2k_workaround_ets.f90
Go to the documentation of this file.
1 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
19 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
20 !-------------------------------------------------------!
21 ! This routine provides a wrapper for the !
22 ! FC2K actor generator to call the actual !
23 ! transport solver routine. !
24 !-------------------------------------------------------!
25 ! Source: --- !
26 ! Developers: D.Kalupin !
27 ! Kontacts: Denis.Kalupin@euro-fusion.org !
28 ! !
29 ! Comments: --- !
30 ! !
31 !-------------------------------------------------------!
32 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
33 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
35  (coreprof_old, coreprof_iter, coreprof_new, &
36  equilibrium_old, equilibrium_iter, &
37  coretransp_iter, &
38  coresource_iter, &
39  coreimpur_iter, &
40  corefast_iter, &
41  control_integer, control_double, &
42 ! CONTROL_INTEGER, CONTROL_DOUBLE, HYPER_DIFF) !AF 25.Apr.2016, 22.Aug.2016
43  hyper_diff,user_out_outputflag,user_out_diagnosticinfo)
44 
45  USE itm_types
46  USE euitm_schemas
47  USE ets_plasma
48  USE ets
49 ! module needed when moving to TRANSPORT_SOLVER
50 ! USE TRANSPORT_SOLVER
51 ! USE ISO_C_BINDING
52 
53  IMPLICIT NONE
54 
55  TYPE (type_coreprof), POINTER :: coreprof_old(:)
56  TYPE (type_coreprof), POINTER :: coreprof_iter(:)
57  TYPE (type_coreprof), POINTER :: coreprof_new(:)
58  TYPE (type_equilibrium), POINTER :: equilibrium_old(:)
59  TYPE (type_equilibrium), POINTER :: equilibrium_iter(:)
60  TYPE (type_coretransp), POINTER :: coretransp_iter(:)
61  TYPE (type_coresource), POINTER :: coresource_iter(:)
62  TYPE (type_coreimpur), POINTER :: coreimpur_iter(:)
63  TYPE (type_corefast), POINTER :: corefast_iter(:)
64 
65  TYPE (type_param) :: code_parameters
66 
67  TYPE (diagnostic) :: diag
68 
69  INTEGER, INTENT(IN) :: control_integer(4) !integer control parameters
70  REAL (R8), INTENT(IN) :: control_double(6) !real control parameters
71 
72 ! +++ Stabilization scheme !AF 25.Apr.2016, 22.Aug.2016
73  REAL (R8), DIMENSION(2) :: hyper_diff !hyper diffusivity
74 
75  integer :: ifail
76  integer :: nch_tmp
77 
78 !---- Diagnostic info ----
79 integer, intent(out) :: user_out_outputflag
80 character(len=:), pointer, intent(out) :: user_out_diagnosticinfo
81 
82 
83 !initial values of diagnostic info
84 user_out_outputflag=0
85 !reset diag type
86 diag%ierr=0
87 diag%error_message=' '
88 
89 ! Call the actual code:
91 ! OLD: ITER: NEW:
92 ! Previous Previous output
93 ! time step iteration
94  (coreprof_old, coreprof_iter, coreprof_new, & !1-D profiles of plasma parameters
95  equilibrium_old, equilibrium_iter, & !Equilibrium quantities / geometry
96  coretransp_iter, & !transport coefficients
97  coresource_iter, & !sources
98  coreimpur_iter, & !impurity species
99  corefast_iter, & !non-thermal components
100 !
101  control_integer, control_double, & !control switches
102 ! CONTROL_INTEGER, CONTROL_DOUBLE, HYPER_DIFF, ifail, & !AF 25.Apr.2016, 22.Aug.2016
103  hyper_diff, & !AF 25.Apr.2016, 22.Aug.2016
104 ! code_parameters)
105  diag) !run diagnostic (errors)
106 
107  if (diag%ierr .lt.0) then
108  user_out_outputflag=diag%ierr
109  nch_tmp=len_trim(diag%error_message)
110  allocate(character(nch_tmp) :: user_out_diagnosticinfo)
111  user_out_diagnosticinfo=diag%error_message(1:nch_tmp)
112  end if
113 
114  RETURN
115 
116 END SUBROUTINE fc2k_transport_solver
117 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
118 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
119 
subroutine transport_solver_interface
Definition: ets.F90:378
subroutine fc2k_transport_solver(COREPROF_OLD,COREPROF_ITER,COREPROF_NEW,EQUILIBRIUM_OLD,EQUILIBRIUM_ITER,CORETRANSP_ITER,CORESOURCE_ITER,COREIMPUR_ITER,COREFAST_ITER,CONTROL_INTEGER,CONTROL_DOUBLE,
Module to cope with problems in fc2k.
Module provides the interface between (external) CPO and internal ETS derived types.
Definition: ets.F90:8
The module declares types of variables used in ETS (transport code)
Definition: ets_plasma.f90:8