SFEMaNS  version 5.3
Reference documentation for SFEMaNS
test_26.f90
Go to the documentation of this file.
1 MODULE test_26
2  IMPLICIT NONE
3  !test 26
4  REAL(KIND=8), PARAMETER:: mu_disk_t26 = 5.d0
5  REAL(KIND=8), PARAMETER:: alpha_t26 = 1.d0
6  INTEGER, PARAMETER :: test_mode_t26 = 4;
7  REAL(KIND=8), PARAMETER:: wjump_t26 = 0.032d0*(1.0d0)
8  REAL(KIND=8), PARAMETER:: zm_t26 = 0.d0, z1_t26 = zm_t26-wjump_t26
9 CONTAINS
10 
11  !====================================================
12  !=======================Extra subroutines for test 26
13 
14  FUNCTION smooth_jump_down_t26(x,x0,x1) RESULT(vv)
15  REAL(KIND=8) :: x,x0,x1
16  REAL(KIND=8) :: vv
17  REAL(KIND=8) :: a0,a1,a2,a3
18  !This function is 1 at x0,
19  !This function is 0 at x1,
20  !Its derivative is 0 at (x1+x0)/2,
21  !Cubic (Factorized)
22 
23  a0 = x1**2*(3*x0-x1)/(x0-x1)**3;
24  a1 = -6.0*x0*x1/(x0-x1)**3;
25  a2 = (3.0*(x0+x1))/(x0-x1)**3;
26  a3 = -2.0/(x0-x1)**3;
27 
28  vv = a0+a1*x+a2*x*x + a3*x*x*x
29  RETURN
30  END FUNCTION smooth_jump_down_t26
31 
32  !derivative with respect to x
33  FUNCTION dsmooth_jump_down_t26(x,x0,x1) RESULT(vv)
34  REAL(KIND=8) :: x,x0,x1
35  REAL(KIND=8) :: vv
36  REAL(KIND=8) :: a0,a1,a2,a3
37  !This function is 1 at x0,
38  !This function is 0 at x1,
39  !Its derivative is 0 at (x1+x0)/2,
40  !Cubic Factorized
41 
42  a0 = x1**2*(3*x0-x1)/(x0-x1)**3;
43  a1 = -6.0*x0*x1/(x0-x1)**3;
44  a2 = (3.0*(x0+x1))/(x0-x1)**3;
45  a3 = -2.0/(x0-x1)**3;
46 
47  vv = a1+2.d0*a2*x + 3.d0*a3*x*x
48  RETURN
49  END FUNCTION dsmooth_jump_down_t26
50 
51  FUNCTION smooth_jump_up_t26(x,x0,x1) RESULT(vv)
52  REAL(KIND=8) :: x,x0,x1
53  REAL(KIND=8) :: vv
54  !This function is 0 at x0,
55  !This function is 1 at x1,
56  !Its derivative is 0 at (x1+x0)/2,
57 
58  vv = 1.d0 - smooth_jump_down_t26( x,x0,x1 );
59  RETURN
60  END FUNCTION smooth_jump_up_t26
61 
62  !derivative with respect to x
63  FUNCTION dsmooth_jump_up_t26(x,x0,x1) RESULT(vv)
64  REAL(KIND=8) :: x,x0,x1
65  REAL(KIND=8) :: vv
66  !This function is 0 at x0,
67  !This function is 1 at x1,
68  !Its derivative is 0 at (x1+x0)/2,
69 
70  vv = - dsmooth_jump_down_t26( x,x0,x1 );
71  RETURN
72  END FUNCTION dsmooth_jump_up_t26
73 
74  FUNCTION mu_func_t26(r,z) RESULT(vv)
75  IMPLICIT NONE
76  REAL(KIND=8) :: r,z
77  REAL(KIND=8) :: vv
78  REAL(KIND=8) :: Fz
79 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
80  !! A smooth jump in z
81 
83  IF ( z.GE.zm_t26 ) THEN
84  vv = 1.d0
85  ELSE IF ( z.LE. z1_t26 ) THEN
86  vv = mu_disk_t26
87  ELSE
88  vv = fz*(mu_disk_t26-1.d0) + 1.d0
89  END IF
90  RETURN
91 
92  !===Dummies variables to avoid warning
93  fz=r
94  !===Dummies variables to avoid warning
95  END FUNCTION mu_func_t26
96 
97  FUNCTION dmu_func_t26(r,z) RESULT(vv)
98  IMPLICIT NONE
99  REAL(KIND=8) :: r,z
100  REAL(KIND=8),DIMENSION(2) :: vv
101  REAL(KIND=8) :: DFz
102 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
103  !! A smooth jump in z
104 
106  IF ( z.GE.zm_t26 ) THEN
107  vv = 0.d0
108  ELSE IF ( z.LE. z1_t26 ) THEN
109  vv = 0.d0
110  ELSE
111  vv(1) = 0
112  vv(2) = dfz*(mu_disk_t26-1.d0)
113  END IF
114  RETURN
115 
116  !===Dummies variables to avoid warning
117  dfz=r
118  !===Dummies variables to avoid warning
119  END FUNCTION dmu_func_t26
120 
121  !===Analytical mu_in_fourier_space (if needed)
122  FUNCTION mu_bar_in_fourier_space_anal_t26(H_mesh,nb,ne,pts,pts_ids) RESULT(vv)
124  USE input_data
125  USE my_util
126  IMPLICIT NONE
127  TYPE(mesh_type) :: H_mesh
128  REAL(KIND=8), DIMENSION(ne-nb+1) :: vv
129  INTEGER :: nb, ne
130  REAL(KIND=8),DIMENSION(2,ne-nb+1),OPTIONAL :: pts
131  INTEGER,DIMENSION(ne-nb+1),OPTIONAL :: pts_ids
132  REAL(KIND=8),DIMENSION(ne-nb+1) :: r,z
133  INTEGER :: n
134 
135  IF( PRESENT(pts) .AND. PRESENT(pts_ids) ) THEN !Computing mu at pts
136  r=pts(1,nb:ne)
137  z=pts(2,nb:ne)
138  ELSE
139  r=h_mesh%rr(1,nb:ne) !Computing mu at nodes
140  z=h_mesh%rr(2,nb:ne)
141  END IF
142 
143  DO n = 1, ne - nb + 1
144  vv(n) = mu_func_t26(r(n),z(n))
145  END DO
146  RETURN
148 
149  !===Analytical mu_in_fourier_space (if needed)
150  FUNCTION grad_mu_bar_in_fourier_space_anal_t26(pt,pt_id) RESULT(vv)
152  USE my_util
153  IMPLICIT NONE
154  REAL(KIND=8),DIMENSION(2) :: vv
155  REAL(KIND=8),DIMENSION(2) :: pt
156  INTEGER,DIMENSION(1) :: pt_id
157  REAL(KIND=8) :: r,z
158  REAL(KIND=8),DIMENSION(2) :: tmp
159  INTEGER :: n
160 
161  r=pt(1)
162  z=pt(2)
163  tmp=dmu_func_t26(r,z)
164  vv(1)=tmp(1)
165  vv(2)=tmp(2)
166  RETURN
167 
168  !===Dummies variables to avoid warning
169  n=pt_id(1)
170  !===Dummies variables to avoid warning
172 
173 END MODULE test_26
real(kind=8) function, dimension(ne-nb+1) mu_bar_in_fourier_space_anal_t26(H_mesh, nb, ne, pts, pts_ids)
Definition: test_26.f90:123
real(kind=8), parameter zm_t26
Definition: test_26.f90:8
real(kind=8) function dsmooth_jump_up_t26(x, x0, x1)
Definition: test_26.f90:64
real(kind=8) function smooth_jump_down_t26(x, x0, x1)
Definition: test_26.f90:15
integer, parameter test_mode_t26
Definition: test_26.f90:6
real(kind=8), parameter wjump_t26
Definition: test_26.f90:7
real(kind=8) function smooth_jump_up_t26(x, x0, x1)
Definition: test_26.f90:52
real(kind=8), parameter mu_disk_t26
Definition: test_26.f90:4
real(kind=8), parameter alpha_t26
Definition: test_26.f90:5
real(kind=8), parameter z1_t26
Definition: test_26.f90:8
real(kind=8) function mu_func_t26(r, z)
Definition: test_26.f90:75
real(kind=8) function, dimension(2) grad_mu_bar_in_fourier_space_anal_t26(pt, pt_id)
Definition: test_26.f90:151
real(kind=8) function, dimension(2) dmu_func_t26(r, z)
Definition: test_26.f90:98
real(kind=8) function dsmooth_jump_down_t26(x, x0, x1)
Definition: test_26.f90:34