ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
pedestal.f90
Go to the documentation of this file.
1 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
7 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
8 MODULE pedestal
9 
10 CONTAINS
11 
12 
13 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
14 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
15  SUBROUTINE main_plasma_pedestal (FUN, RHO, RHO_PED, PSI, NRHO)
16 
17 !-------------------------------------------------------!
18 ! This routine provides artificial pedestal !
19 ! in profiles of plasma parameters which are not !
20 ! solved up to the separatrix. !
21 !-------------------------------------------------------!
22 ! Source: --- !
23 ! Developers: D.Kalupin !
24 ! Kontacts: Denis.Kalupin@efda.org !
25 ! !
26 ! Ref.: `Snyder, PPCF 46 (2004), A131` !
27 ! !
28 !-------------------------------------------------------!
29 
30 
31  USE itm_types
32  USE ets_plasma
33 
34  IMPLICIT NONE
35 
36 ! +++ Internal ETS derived types:
37  TYPE (magnetic_geometry) :: geometry !contains all geometry quantities
38  TYPE (plasma_profiles) :: profiles !contains profiles of plasma parameters
39 
40 
41 ! +++ Dimensions:
42  INTEGER :: nrho,irho !number of radial points
43  INTEGER :: nped
44 
45 
46 ! +++ Parameters:
47  REAL (R8), INTENT(INOUT) :: fun(nrho)
48  REAL (R8), INTENT(IN) :: rho(nrho)
49  REAL (R8), INTENT(IN) :: psi(nrho)
50  REAL (R8), INTENT(IN) :: rho_ped
51  REAL (R8) :: psi_mid
52  REAL (R8) :: delta
53 !-------------------------------------------------------!
54 
55 ! +++ Determine the index of pedestal top
56  DO irho = 1, nrho
57  IF (rho(irho).GT.rho_ped) EXIT
58  nped = irho
59  END DO
60 
61  psi_mid = (psi(nped) + psi(nrho)) / 2.0_r8
62  delta = abs(psi(nped) - psi(nrho))
63 
64 ! +++ Determine the index of pedestal top
65  DO irho = nped+1, nrho
66  fun(irho) = fun(nped) + (fun(nped)-fun(nrho)) * &
67  (tanh(2.0_r8*(1.0_r8-psi_mid)/delta)-tanh(2.0_r8*(psi(irho)-psi_mid)/delta))
68  END DO
69 
70  RETURN
71 
72 
73 
74  END SUBROUTINE main_plasma_pedestal
75 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
76 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
77 
78 
79 
80 
81 
82 END MODULE pedestal
83 
Module provides the interface between (external) CPO and internal ETS derived types.
Definition: pedestal.f90:8
subroutine profiles(p0, rbphi, dp0, drbphi, a)
Definition: profiles.f90:1
subroutine fun(X, F)
Definition: Ev2.f:10
subroutine main_plasma_pedestal(FUN, RHO, RHO_PED, PSI, NRHO)
Definition: pedestal.f90:15
The module declares types of variables used in ETS (transport code)
Definition: ets_plasma.f90:8