SFEMaNS  version 4.1 (work in progress)
Reference documentation for SFEMaNS
 All Classes Files Functions Variables Groups Pages
test_18.f90
Go to the documentation of this file.
1 MODULE test_18
2  IMPLICIT NONE
3  !TEST 18
4  REAL (KIND=8), PARAMETER, PUBLIC :: lambda_mu_T18=10.0d0
5 CONTAINS
6  FUNCTION mu_bar_in_fourier_space_anal_t18(H_mesh,nb,ne,pts,pts_ids) RESULT(vv)
7  USE def_type_mesh
8  USE input_data
9  USE my_util
10 
11  IMPLICIT NONE
12  TYPE(mesh_type) :: h_mesh
13  REAL(KIND=8), DIMENSION(ne-nb+1) :: vv
14  INTEGER :: nb, ne
15  REAL(KIND=8),DIMENSION(2,ne-nb+1),OPTIONAL :: pts
16  INTEGER,DIMENSION(ne-nb+1),OPTIONAL :: pts_ids
17  INTEGER, DIMENSION(H_mesh%np) :: global_ids
18  INTEGER, DIMENSION(ne-nb+1) :: local_ids
19  INTEGER :: n,m
20  REAL(KIND=8),DIMENSION(ne-nb+1) :: r,z
21 
22  IF( present(pts) .AND. present(pts_ids) ) THEN !Computing mu at pts
23  r=pts(1,nb:ne)
24  z=pts(2,nb:ne)
25  local_ids=pts_ids
26  ELSE
27  r=h_mesh%rr(1,nb:ne) !Computing mu at nodes
28  z=h_mesh%rr(2,nb:ne)
29  DO m = 1, h_mesh%me
30  global_ids(h_mesh%jj(:,m)) = h_mesh%i_d(m)
31  END DO
32  local_ids=global_ids(nb:ne)
33  END IF
34 
35  DO n = 1, ne - nb + 1
36  IF(local_ids(n)==1) THEN
37  vv(n) = 1.d0 + r(n) !mu1 , DCQ: If you change mu1_bar, you have to change
38  !Jexact_gauss() as well
39  ELSE
40  vv(n) = 1.d0 + r(n) + 2*lambda_mu_t18*(1+r(n))/(z(n)**2*(3*r(n)+2)) !mu2
41  END IF
42  END DO
43  RETURN
45 
46  !===Analytical grad_bar_mu_in_fourier_space (if needed)
47  FUNCTION grad_mu_bar_in_fourier_space_anal_t18(pt,pt_id) RESULT(vv)
48  USE input_data
49  USE my_util
50  IMPLICIT NONE
51  REAL(KIND=8),DIMENSION(2) :: pt,vv
52  INTEGER,DIMENSION(1) :: pt_id
53  REAL(KIND=8) :: r,z
54 
55  r=pt(1)
56  z=pt(2)
57 
58  IF(pt_id(1)==1) THEN !grad_mu_1
59  vv(1)= 1.d0
60  vv(2)= 0.d0
61  ELSE !grad_mu_2
62  vv(1)=1.d0 + ( (3*r+2)*(2*lambda_mu_t18) - ( (2*lambda_mu_t18*(1+r)))*(3) ) /( z*(3*r+2) )**2
63  vv(2)= (2*lambda_mu_t18*(1+r))/(3*r+2)*(-2/z**3)
64  END IF
65  RETURN
67 
68 END MODULE test_18
real(kind=8) function, dimension(ne-nb+1) mu_bar_in_fourier_space_anal_t18(H_mesh, nb, ne, pts, pts_ids)
Definition: test_18.f90:6
real(kind=8) function, dimension(2) grad_mu_bar_in_fourier_space_anal_t18(pt, pt_id)
Definition: test_18.f90:47
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