SFEMaNS  version 5.3
Reference documentation for SFEMaNS
def_type_mesh.f90
Go to the documentation of this file.
1 !
2 !Authors: Jean-Luc Guermond, Copyright 2000
3 !
5  USE dyn_line
6  IMPLICIT NONE
7 
8  TYPE aij_type
9  INTEGER, POINTER, DIMENSION(:) :: ia, ja
10  END TYPE aij_type
11 
13  INTEGER :: nb_periodic_pairs
14  INTEGER, DIMENSION(:,:), POINTER :: list_periodic
15  REAL(KIND=8), DIMENSION(:,:), POINTER :: vect_e
16  END TYPE periodic_data
17 
19  INTEGER, DIMENSION(:), POINTER :: ia, ja
20  INTEGER, DIMENSION(:,:), POINTER :: loc_to_glob
21  INTEGER :: kmax
22  INTEGER, DIMENSION(:), POINTER :: np
23  INTEGER, DIMENSION(:), POINTER :: dom_np
24  END TYPE petsc_csr_la
25 
26  !------------------------------------------------------------------------------
27  ! REAL(KIND=8), DIMENSION(n_w, l_G), PUBLIC :: ww
28  ! REAL(KIND=8), DIMENSION(n_ws, l_Gs), PUBLIC :: wws
29  ! REAL(KIND=8), DIMENSION(k_d, n_w, l_G, me), PUBLIC :: dw
30  ! REAL(KIND=8), DIMENSION(n_w,l_G,1:2,me), PUBLIC :: dwni !d/dn, interface (JLG, April 2009)
31  ! REAL(KIND=8), DIMENSION(k_d, l_Gs, mes), PUBLIC :: rnorms
32  ! REAL(KIND=8), DIMENSION(l_G, me), PUBLIC :: rj
33  ! REAL(KIND=8), DIMENSION(l_Gs, mes), PUBLIC :: rjs
34  ! REAL(KIND=8), DIMENSION(k_d, n_w, l_Gs, mes) :: dw_s !gradient at the boundary
35  !------------------------------------------------------------------------------
36 
38  INTEGER :: k_d, n_w, l_g, n_ws, l_gs
39  REAL(KIND=8), DIMENSION(:, :), POINTER :: ww
40  REAL(KIND=8), DIMENSION(:, :), POINTER :: wws
41  REAL(KIND=8), DIMENSION(:, :), POINTER :: wwsi !Interface shape function (JLG, June 4 2012)
42  REAL(KIND=8), DIMENSION(:, :, :, :), POINTER :: dw
43  REAL(KIND=8), DIMENSION(:, :, :, :), POINTER :: dwni !Interface gradient (JLG, April 2009)
44  REAL(KIND=8), DIMENSION(:, :, :), POINTER :: rnorms
45  REAL(KIND=8), DIMENSION(:, :, :), POINTER :: rnorms_v !(JLG Aug 31, 2017)
46  REAL(KIND=8), DIMENSION(:, :, :, :), POINTER :: rnormsi !Interface normal (JLG, June 4 2012)
47  REAL(KIND=8), DIMENSION(:, :), POINTER :: rj !Interface weight (JLG, April 2009)
48  REAL(KIND=8), DIMENSION(:, :), POINTER :: rji
49  REAL(KIND=8), DIMENSION(:, :), POINTER :: rjs
50  REAL(KIND=8), DIMENSION(:, :, :, :), POINTER :: dw_s !gradient at the boundary
51  REAL(KIND=8), DIMENSION(:, :, :, :), POINTER :: dwps !special!
52  REAL(KIND=8), DIMENSION(:, :, :, :), POINTER :: dws !SPECIAL!
53  END TYPE gauss_type
54 
56  TYPE(dyn_int_line), DIMENSION(20) :: list
57  TYPE(dyn_int_line), DIMENSION(20) :: perlist
58  INTEGER, POINTER, DIMENSION(: ) :: pnt
59  INTEGER :: n_bord
60  END TYPE periodic_type
61 
62  !------------------------------------------------------------------------------
63  ! loc_to_glob(np) gives global numbering from local numbering on current processor
64  ! jj(n_w, me) nodes of the volume_elements
65  ! jji(n_w, 1:2, mi) edge to node conectivity array --> volume numbering (JLG April 2009)
66  ! neighi(1:2, mi) interfaces to volume elements --> cell 1 has lowest cell number
67  ! jjsi(n_ws, mi) nodes of the interface elements --> volume numbering (JLG April 2009)
68  ! jjs(n_ws, mes) nodes of the surface_elements --> volume numbering
69  ! iis(n_ws, mes) nodes of the surface_elements --> surface numbering
70  ! mm(me) (possibly sub) set of elements for quadrature
71  ! mms(mes) (possibly sub) set of surface_elements for surf_quadrature
72  !------------------------------------------------------------------------------
73 
74  TYPE mesh_type
75  INTEGER, POINTER, DIMENSION(:,:) :: jj, jjs, iis
76  INTEGER, POINTER,DIMENSION(:,:,:):: jji ! (JLG April 2009)
77  INTEGER, POINTER, DIMENSION(:,:) :: jjsi ! (JLG April 2009)
78  INTEGER, POINTER, DIMENSION(:) :: j_s ! boundary nodes --> volume numbering
79  REAL(KIND=8), POINTER, DIMENSION(:,:) :: rr
80  INTEGER, POINTER, DIMENSION(:,:) :: neigh
81  INTEGER, POINTER, DIMENSION(:,:) :: neighi ! (JLG April 2009)
82  INTEGER, POINTER, DIMENSION(:) :: sides, neighs
83  INTEGER, POINTER, DIMENSION(:) :: i_d
84  !==Parallel structure
85  INTEGER, POINTER, DIMENSION(:) :: loc_to_glob ! (JLG+FL, January 2011)
86  INTEGER, POINTER, DIMENSION(:) :: disp, domnp ! (JLG+FL, January 2011)
87  INTEGER :: dom_me, dom_np, dom_mes ! (JLG+FL, January 2011)
88  ! dom_me and dom_mes are obsolete structures.
89  ! dom_np is the number of nodes owned by the processor: dom_np .LE. mesh%np
90  !==End parallel structure
91  INTEGER :: me, mes, np, nps, mi
92  LOGICAL :: edge_stab ! edge stab, yes/no, (JLG April 2009)
93  TYPE(gauss_type) :: gauss
95  REAL(KIND=8), POINTER, DIMENSION(:) :: hloc ! local mesh size (JLG+LC January, 21, 2015)
96  REAL(KIND=8), POINTER, DIMENSION(:) :: hloc_gauss ! local mesh size (JLG+LC January, 21, 2015)
97  REAL(KIND=8) :: global_diameter !diameter of domain (LC 2017/01/27)
98  REAL(KIND=8), POINTER, DIMENSION(:) :: hm !local meshsize in azimuth (JLG April 7, 2017)
99  END TYPE mesh_type
100 
102  INTEGER, POINTER, DIMENSION(:) :: slave_elem ! list slave elemt in interface
103  INTEGER, POINTER, DIMENSION(:) :: list_slave_node ! list of slave nodes on interface
104  INTEGER, POINTER, DIMENSION(:,:) :: master_node ! local --> global numbering; master nodes
105  INTEGER, POINTER, DIMENSION(:,:) :: slave_node ! local --> global numbering; slave nodes
106  INTEGER :: me ! nb of slave elemt in interface
107  END TYPE mesh_type_interface
108 
110  INTEGER, POINTER, DIMENSION(:) :: master ! list master boundary elemts
111  INTEGER, POINTER, DIMENSION(:) :: slave ! list slave boundary elemts not in interface
112  INTEGER, POINTER, DIMENSION(:) :: interface ! list slave boundary elemts in the interface
113  INTEGER, POINTER, DIMENSION(:,:) :: master_node ! local --> global numbering; master nodes
114  END TYPE mesh_type_boundary
115 
117  INTEGER :: mes ! number of interface elements
118  INTEGER, POINTER, DIMENSION(:) :: mesh1 ! list slave interface elements
119  INTEGER, POINTER, DIMENSION(:) :: mesh2 ! list master interface elements
120  INTEGER, POINTER, DIMENSION(:,:) :: jjs1 ! list of slave node on interface elements
121  INTEGER, POINTER, DIMENSION(:,:) :: jjs2 ! list of master nodes on interface elements
122  END TYPE interface_type
123 
124 
125 END MODULE def_type_mesh
integer, public k_d
integer, public l_g
integer, public l_gs
integer, public n_ws
real(kind=8), dimension(:,:), pointer rj
real(kind=8), dimension(:,:,:), pointer rnorms
integer, public n_w
real(kind=8), dimension(:,:,:,:), pointer dws
real(kind=8), dimension(:,:,:,:), pointer dwps
real(kind=8), dimension(:,:), pointer rjs
real(kind=8), dimension(:,:), pointer wws
subroutine gauss(mesh)
real(kind=8), dimension(:,:,:,:), pointer dw
real(kind=8), dimension(:,:), pointer ww
real(kind=8), dimension(:,:,:,:), pointer dw_s