SFEMaNS  version 4.1 (work in progress)
Reference documentation for SFEMaNS
 All Classes Files Functions Variables Groups Pages
test_22.f90
Go to the documentation of this file.
1 MODULE test_22
2  IMPLICIT NONE
3  !TEST 22
4  REAL (KIND=8), PARAMETER, PUBLIC :: ratio_mu_T22 = 50.d0 ! the variation of mu
5  REAL (KIND=8), PUBLIC :: b_factor_T22 = (2**6) * (ratio_mu_T22-1.d0)/(ratio_mu_T22+1.d0)
6  INTEGER, PUBLIC :: mode_mu_T22 = 4
7 
8 CONTAINS
9 
10  FUNCTION f_test_t22(r,z) RESULT(vv)
11  IMPLICIT NONE
12  REAL(KIND=8), DIMENSION(:), INTENT(IN) :: r, z
13  REAL(KIND=8), DIMENSION(SIZE(r)) :: vv
14  vv = b_factor_t22*(r*(1-r)*(z**2-1))**3
15  RETURN
16  END FUNCTION f_test_t22
17 
18  FUNCTION dfdr_test_t22(r,z) RESULT(vv)
19  IMPLICIT NONE
20  REAL(KIND=8), INTENT(IN):: r, z
21  REAL(KIND=8) :: vv
22  vv = 3 * b_factor_t22 * (z**2-1)**3 * (r*(1-r))**2 * (1-2*r)
23  RETURN
24  END FUNCTION dfdr_test_t22
25 
26  FUNCTION dfdz_test_t22(r,z) RESULT(vv)
27  IMPLICIT NONE
28  REAL(KIND=8), INTENT(IN):: r, z
29  REAL(KIND=8) :: vv
30  vv = 3*b_factor_t22*(r*(1-r))**3*(z**2-1)**2*(2*z)
31  RETURN
32  END FUNCTION dfdz_test_t22
33 
34  !===Analytical mu_in_fourier_space (if needed)
35  FUNCTION mu_bar_in_fourier_space_anal_t22(H_mesh,nb,ne,pts,pts_ids) RESULT(vv)
36  USE def_type_mesh
37  USE input_data
38  USE my_util
39  IMPLICIT NONE
40  TYPE(mesh_type) :: h_mesh
41  REAL(KIND=8), DIMENSION(ne-nb+1) :: vv
42  INTEGER :: nb, ne
43  REAL(KIND=8),DIMENSION(2,ne-nb+1),OPTIONAL :: pts
44  INTEGER, DIMENSION(ne-nb+1), OPTIONAL :: pts_ids
45  REAL(KIND=8),DIMENSION(ne-nb+1) :: r,z
46 
47  IF( present(pts) .AND. present(pts_ids) ) THEN !Computing mu at pts
48  r=pts(1,nb:ne)
49  z=pts(2,nb:ne)
50  ELSE
51  r=h_mesh%rr(1,nb:ne) !Computing mu at nodes
52  z=h_mesh%rr(2,nb:ne)
53  END IF
54 
55  vv=1.d0/(1.d0+abs(f_test_t22(r,z)))
56  RETURN
58 
59  !===Analytical mu_in_fourier_space (if needed)
60  FUNCTION grad_mu_bar_in_fourier_space_anal_t22(pt,pt_id) RESULT(vv)
61  USE input_data
62  USE my_util
63  IMPLICIT NONE
64  REAL(KIND=8),DIMENSION(2) :: pt,vv
65  INTEGER,DIMENSION(1) :: pt_id
66  REAL(KIND=8),DIMENSION(1) :: tmp,r,z
67  REAL(KIND=8) :: sign
68  INTEGER :: n
69 
70  r(1)=pt(1)
71  z(1)=pt(2)
72  tmp=f_test_t22(r,z)
73  IF (tmp(1) .GE. 0.d0 ) THEN
74  sign =1.0
75  ELSE
76  sign =-1.0
77  END IF
78 
79  vv(1)=-sign*dfdr_test_t22(r(1),z(1))/(1.d0 +abs(tmp(1)))**2
80  vv(2)=-sign*dfdz_test_t22(r(1),z(1))/(1.d0 +abs(tmp(1)))**2
81  RETURN
82 
83  !===Dummies variables to avoid warning
84  n=pt_id(1)
85  !===Dummies variables to avoid warning
87 
88  FUNCTION mu_in_real_space_anal_t22(H_mesh,angles,nb_angles,nb,ne) RESULT(vv)
89  USE def_type_mesh
90  IMPLICIT NONE
91  TYPE(mesh_type) :: h_mesh
92  REAL(KIND=8), DIMENSION(:) :: angles
93  INTEGER :: nb_angles
94  INTEGER :: nb, ne
95  REAL(KIND=8), DIMENSION(nb_angles,ne-nb+1) :: vv
96  INTEGER :: ang
97 
98  DO ang = 1, nb_angles
99  vv(ang,:) = 1/(1+f_test_t22(h_mesh%rr(1,nb:ne),h_mesh%rr(2,nb:ne))*cos(mode_mu_t22*angles(ang)))
100  END DO
101  RETURN
102  END FUNCTION mu_in_real_space_anal_t22
103 
104 END MODULE test_22
real(kind=8) function, dimension(ne-nb+1) mu_bar_in_fourier_space_anal_t22(H_mesh, nb, ne, pts, pts_ids)
Definition: test_22.f90:35
real(kind=8) function dfdr_test_t22(r, z)
Definition: test_22.f90:18
real(kind=8) function, dimension(size(r)) f_test_t22(r, z)
Definition: test_22.f90:10
real(kind=8) function, dimension(2) grad_mu_bar_in_fourier_space_anal_t22(pt, pt_id)
Definition: test_22.f90:60
real(kind=8) function dfdz_test_t22(r, z)
Definition: test_22.f90:26
real(kind=8) function, dimension(nb_angles, ne-nb+1) mu_in_real_space_anal_t22(H_mesh, angles, nb_angles, nb, ne)
Definition: test_22.f90:88
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