SFEMaNS  version 4.1 (work in progress)
Reference documentation for SFEMaNS
 All Classes Files Functions Variables Groups Pages
test_27.f90
Go to the documentation of this file.
1 MODULE test_27
2  IMPLICIT NONE
3  !TEST 27
4  !DCQ Test mu_var_theta_vaccuum
5  REAL (kind=8),PARAMETER,PUBLIC :: ratio_mu_T27 = 50.0d0 ! the variation of mu
6  REAL (kind=8),PUBLIC :: b_factor_T27 = (2**6) * (ratio_mu_T27-1.d0)/(ratio_mu_T27+1.d0)
7  INTEGER, PUBLIC :: mode_mu_T27 = 4
8  REAL (kind=8),PUBLIC :: omega_T27 = 1.d0
9 CONTAINS
10 
11  !===Analytical mu_in_fourier_space (if needed)
12  FUNCTION mu_bar_in_fourier_space_anal_t27(H_mesh,nb,ne,pts,pts_ids) RESULT(vv)
13  USE def_type_mesh
14  USE input_data
15  USE my_util
16  IMPLICIT NONE
17  TYPE(mesh_type) :: h_mesh
18  REAL(KIND=8), DIMENSION(ne-nb+1) :: vv
19  INTEGER :: nb, ne
20  REAL(KIND=8),DIMENSION(2,ne-nb+1),OPTIONAL :: pts
21  INTEGER,DIMENSION(ne-nb+1),OPTIONAL :: pts_ids
22  REAL(KIND=8),DIMENSION(ne-nb+1) :: r,z
23 
24  IF( present(pts) .AND. present(pts_ids) ) THEN !Computing mu at pts
25  r=pts(1,nb:ne)
26  z=pts(2,nb:ne)
27  ELSE
28  r=h_mesh%rr(1,nb:ne) !Computing mu at nodes
29  z=h_mesh%rr(2,nb:ne)
30  END IF
31 
32  vv=1.d0/(1.d0+abs(f_test_t27(r,z)))
33  RETURN
35 
36  !===Analytical mu_in_fourier_space (if needed)
37  FUNCTION grad_mu_bar_in_fourier_space_anal_t27(pt,pt_id) RESULT(vv)
38  USE input_data
39  USE my_util
40  IMPLICIT NONE
41  REAL(KIND=8),DIMENSION(2) :: pt,vv
42  INTEGER,DIMENSION(1) :: pt_id
43  REAL(KIND=8),DIMENSION(1) :: tmp,r,z
44  REAL(KIND=8) :: sign
45  INTEGER :: n
46 
47  r(1)=pt(1)
48  z(1)=pt(2)
49  tmp=f_test_t27(r,z)
50 
51  IF (tmp(1) .GE. 0.d0 ) THEN
52  sign =1.0
53  ELSE
54  sign =-1.0
55  END IF
56 
57  vv(1)=-sign*dfdr_test_t27(r(1),z(1))/(1.d0 +abs(tmp(1)))**2
58  vv(2)=-sign*dfdz_test_t27(r(1),z(1))/(1.d0 +abs(tmp(1)))**2
59  RETURN
60 
61  !===Dummies variables to avoid warning
62  n=pt_id(1)
63  !===Dummies variables to avoid warning
65 
66  FUNCTION mu_in_real_space_anal_t27(H_mesh,angles,nb_angles,nb,ne,time) RESULT(vv)
67  USE def_type_mesh
68  IMPLICIT NONE
69  TYPE(mesh_type) :: h_mesh
70  REAL(KIND=8), DIMENSION(:) :: angles
71  INTEGER :: nb_angles
72  INTEGER :: nb, ne
73  REAL(KIND=8) :: time
74  REAL(KIND=8), DIMENSION(nb_angles,ne-nb+1) :: vv
75  INTEGER :: ang
76 
77  DO ang = 1, nb_angles
78  vv(ang,:) = 1/(1+f_test_wtime_t27(h_mesh%rr(1,nb:ne),h_mesh%rr(2,nb:ne),time)*cos(mode_mu_t27*angles(ang)))
79  END DO
80  END FUNCTION mu_in_real_space_anal_t27
81 
82  FUNCTION f_test_t27(r,z) RESULT(vv)
83  IMPLICIT NONE
84  REAL(KIND=8), DIMENSION(:), INTENT(IN) :: r, z
85  REAL(KIND=8), DIMENSION(SIZE(r)) :: vv
86 
87  vv = b_factor_t27*(r*(1-r)*(z**2-1))**3
88  RETURN
89  END FUNCTION f_test_t27
90 
91  FUNCTION f_test_wtime_t27(r,z,t) RESULT(vv)
92  IMPLICIT NONE
93  REAL(KIND=8), DIMENSION(:), INTENT(IN) :: r, z
94  REAL(KIND=8), INTENT(IN) :: t
95  REAL(KIND=8), DIMENSION(SIZE(r)) :: vv
96 
97  vv = b_factor_t27*cos(omega_t27*t)*(r*(1-r)*(z**2-1))**3
98  RETURN
99  END FUNCTION f_test_wtime_t27
100 
101  FUNCTION dfdr_test_t27(r,z) RESULT(vv)
102  IMPLICIT NONE
103  REAL(KIND=8), INTENT(IN):: r, z
104  REAL(KIND=8) :: vv
105  vv = 3 * b_factor_t27 * (z**2-1)**3 * (r*(1-r))**2 * (1-2*r)
106  RETURN
107  END FUNCTION dfdr_test_t27
108 
109  FUNCTION dfdr_test_wtime_t27(r,z, t) RESULT(vv)
110  IMPLICIT NONE
111  REAL(KIND=8), INTENT(IN):: r, z,t
112  REAL(KIND=8) :: vv
113  vv = 3 * b_factor_t27 * cos(omega_t27*t) * (z**2-1)**3 * (r*(1-r))**2 * (1-2*r)
114  RETURN
115  END FUNCTION dfdr_test_wtime_t27
116 
117  FUNCTION dfdz_test_t27(r,z) RESULT(vv)
118  IMPLICIT NONE
119  REAL(KIND=8), INTENT(IN):: r, z
120  REAL(KIND=8) :: vv
121  vv = 3*b_factor_t27*(r*(1-r))**3*(z**2-1)**2*(2*z)
122  RETURN
123  END FUNCTION dfdz_test_t27
124 
125  FUNCTION dfdz_test_wtime_t27(r,z,t) RESULT(vv)
126  IMPLICIT NONE
127  REAL(KIND=8), INTENT(IN):: r, z,t
128  REAL(KIND=8) :: vv
129  vv = 3*b_factor_t27*cos(omega_t27*t) *(r*(1-r))**3*(z**2-1)**2*(2*z)
130  RETURN
131  END FUNCTION dfdz_test_wtime_t27
132 
133 END MODULE test_27
section doc_intro_frame_work_num_app Numerical approximation subsection doc_intro_fram_work_num_app_Fourier_FEM Fourier Finite element representation The SFEMaNS code uses a hybrid Fourier Finite element formulation The Fourier decomposition allows to approximate the problem’s solutions for each Fourier mode modulo nonlinear terms that are made explicit The variables are then approximated on a meridian section of the domain with a finite element method The numerical approximation of a function f $f f is written in the following generic t
Definition: doc_intro.h:199
real(kind=8) function dfdz_test_wtime_t27(r, z, t)
Definition: test_27.f90:125
real(kind=8) function, dimension(size(r)) f_test_t27(r, z)
Definition: test_27.f90:82
real(kind=8) function, dimension(2) grad_mu_bar_in_fourier_space_anal_t27(pt, pt_id)
Definition: test_27.f90:37
real(kind=8) function, dimension(ne-nb+1) mu_bar_in_fourier_space_anal_t27(H_mesh, nb, ne, pts, pts_ids)
Definition: test_27.f90:12
real(kind=8) function dfdr_test_wtime_t27(r, z, t)
Definition: test_27.f90:109
real(kind=8) function, dimension(nb_angles, ne-nb+1) mu_in_real_space_anal_t27(H_mesh, angles, nb_angles, nb, ne, time)
Definition: test_27.f90:66
real(kind=8) function dfdz_test_t27(r, z)
Definition: test_27.f90:117
real(kind=8) function, dimension(size(r)) f_test_wtime_t27(r, z, t)
Definition: test_27.f90:91
section doc_intro_frame_work_num_app Numerical approximation subsection doc_intro_fram_work_num_app_Fourier_FEM Fourier Finite element representation The SFEMaNS code uses a hybrid Fourier Finite element formulation The Fourier decomposition allows to approximate the problem’s solutions for each Fourier mode modulo nonlinear terms that are made explicit The variables are then approximated on a meridian section of the domain with a finite element method The numerical approximation of a function f $f f is written in the following generic z
Definition: doc_intro.h:193
real(kind=8) function dfdr_test_t27(r, z)
Definition: test_27.f90:101