ICFERST  22-06
Reservoir simulator based on DCVFEM, Dynamic Mesh optimisation and Surface-based modelling
multi_shape_fct_ND.F90 File Reference
#include "fdebug.h"
Include dependency graph for multi_shape_fct_ND.F90:

Data Types

interface  shape_functions_linear_quadratic::detnlxr
 : Calculates the derivatives of the shape functions More...
 
interface  shape_functions_linear_quadratic::detnlxr_invjac
 : Computes the derivatives of the shape functions and the inverse of the Jacobian More...
 
interface  shape_functions_ndim::xprod
 Performs the cross product of two vectors. More...
 

Modules

module  shape_functions_linear_quadratic
 Shape function subroutines for multi-dimensions for Quadrilaterals, Triangles, Hexaedra and Tetrahedra.
 
module  shape_functions_ndim
 This module contains subroutines to generate the shape functions for multi dimensions.
 

Functions/Subroutines

subroutine shape_functions_linear_quadratic::re2dn4 (lowqua, ngi, ngi_l, nloc, mloc, m, weight, n, nlx, nly, sngi, snloc, sweigh, sn, snlx, l1, l2)
 at the Gauss points. NB: We may need to define surface elements for p and (u,v,w) More...
 
subroutine shape_functions_linear_quadratic::re3dn8 (lowqua, ngi, ngi_l, nloc, mloc, m, weight, n, nlx, nly, nlz, sngi, snloc, sweigh, sn, snlx, snly, l1, l2, l3)
 This subrt. computes the shape functions M and N and their derivatives at the Gauss points for 3D. If LOWQUA, then use one point quadrature else use 8 point quadrature. NB.: LX/YP(I) are the local X/Y coordinates of nodal point I. More...
 
subroutine shape_functions_linear_quadratic::re2dn9 (lowqua, ngi, ngi_l, nloc, mloc, m, weight, n, nlx, nly, l1, l2)
 Quadratic variation (2D) for velocity – 9 node brick element. Linear variation (2D) for pressure – 4 node brick element. NB.: We may need to define surface elements for p and (u,v,w). More...
 
subroutine shape_functions_linear_quadratic::re3d27 (lowqua, ngi, ngi_l, nloc, mloc, m, weight, n, nlx, nly, nlz, l1, l2, l3)
 Quadratic variation (3D) for velocity – 27 node brick element. Linear variation (3D) for pressure – 8 node brick element. NB.: We may need to define surface elements for p and (u,v,w). More...
 
subroutine shape_functions_linear_quadratic::retrieve_ngi_old (ndim, cv_ele_type, cv_nloc, u_nloc, cv_ngi, cv_ngi_short, scvngi, sbcvngi, nface, QUAD_OVER_WHOLE_ELE)
 Obtains the gauss integration numbers given the input parameters use retrieve_ngi instead of this one since it uses data types retrieve_ngi. More...
 
subroutine shape_functions_linear_quadratic::retrieve_ngi (GIdims, Mdims, cv_ele_type, QUAD_OVER_WHOLE_ELE, scalar_nloc, vector_nloc)
 : Computes the number of Gauss integration points and all the necessary information More...
 
subroutine shape_functions_linear_quadratic::lagrot (weit, quadpos, ndgi, getndp)
 This computes the weight and points for standard Gaussian quadrature. If (GETNDP == T) then get the position of the nodes and neglect the weights. More...
 
real function shape_functions_linear_quadratic::lagran (diff, lx, inod, ndnod, nodpos)
 This return the Lagrange poly assocaited with node INOD at point LX If DIFF then send back the value of this poly differentiated. More...
 
real function shape_functions_linear_quadratic::rgptwe (IG, ND, WEIGHT)
 If WEIGHT is TRUE in function RGPTWE then return the Gauss-pt weight else return the Gauss-pt. There are ND Gauss points – we are looking for either the weight or the x-coord of the IG'th Gauss point. More...
 
subroutine shape_functions_linear_quadratic::quad_basis_funs_1d (sngi, snloc, sweigh, sn, snlx)
 determine the 1d shape functions sn and its local derivative slnx. More...
 
subroutine shape_functions_ndim::quad_1d_shape (cv_ngi, cv_nloc, u_nloc, cvn, cvweigh, n, nlx, un, unlx)
 : For quadratic elements. Shape functions associated with volume integration using both CV basis functions CVN as well as FEM basis functions N (and its derivatives NLX, NLY, NLZ) More...
 
subroutine shape_functions_ndim::quad_nd_shape (ndim, cv_ele_type, cv_ngi, cv_nloc, u_nloc, cvn, cvweigh, n, nlx, nly, nlz, un, unlx, unly, unlz)
 : For quadratic elements: Shape functions associated with volume integration using both CV (CVN) and FEM (N and its derivatives NLX/Y/Z) basis functions. More...
 
subroutine shape_functions_ndim::quad_nd_shape_n (cv_ele_type, ndim, cv_ngi, cv_nloc, cvn, cvweigh, n, nlx, nly, nlz, cv_ngi_1d, cv_nloc_1d, cvn_1d, cvweigh_1d, n_1d, nlx_1d)
 : For quadatic elements – shape functions associated with volume integration using both CV basis functions CVN as well as FEM basis functions N (and its derivatives NLX, NLY, NLZ) More...
 
subroutine shape_functions_ndim::vol_cv_tri_tet_shape (cv_ele_type, ndim, cv_ngi, cv_nloc, u_nloc, cvn, cvweigh, n, nlx, nly, nlz, un, unlx, unly, unlz)
 : Compute shape functions N, UN etc for linear trianles. Shape functions associated with volume integration using both CV basis functions CVN, as well as FEM basis functions N (and its derivatives NLX, NLY, NLZ). Also for velocity basis functions UN, UNLX, UNLY, UNLZ. More...
 
subroutine shape_functions_ndim::new_pt_qua_vol_cv_tri_tet_shape (cv_ele_type, ndim, cv_ngi, cv_nloc, u_nloc, cvn, cvweigh, n, nlx, nly, nlz, un, unlx, unly, unlz)
 : new 1 or 4 pt quadrature set on each CV of a quadratic tetrahedra ..... Compute shape functions N, UN etc for linear trianles. Shape functions associated with volume integration using both CV basis functions CVN, as well as FEM basis functions N (and its derivatives NLX, NLY, NLZ). Also for velocity basis functions UN, UNLX, UNLY, UNLZ. More...
 
subroutine shape_functions_ndim::test_quad_tet (cv_nloc, cv_ngi, cvn, n, nlx, nly, nlz, cvweight, x, y, z, x_nonods, x_ndgln2, totele)
 test the volumes of idealised triangle More...
 
subroutine shape_functions_ndim::compute_xndgln_tritetquadhex (cv_ele_type, max_totele, max_x_nonods, quad_cv_nloc, totele, x_nonods, x_ndgln, lx, ly, lz, x, y, z, fem_nod, x_ideal, y_ideal, z_ideal, x_ndgln_ideal)
 Get the x_ndgln for the nodes of triangles or tetrahedra. More...
 
subroutine shape_functions_ndim::suf_cv_tri_tet_shape (cv_ele_type, ndim, scvngi, cv_nloc, u_nloc, scvfeweigh, scvfen, scvfenlx, scvfenly, scvfenlz, scvfenslx, scvfensly, sufen, sufenlx, sufenly, sufenlz, sufenslx, sufensly, cv_neiloc, cvfem_neiloc, ufem_neiloc)
 : Compute shape functions N, UN etc for linear triangles. Shape functions associated with volume integration using both CV basis functions CVN, as well as FEM basis functions SN (and its derivatives SNLX, SNLY, SNLZ). Also for velocity basis functions SUN, SUNLX, SUNLY, SUNLZ. Also the derivatives along the CV faces: sufnlx, sufnly, sufunlx, sufunly More...
 
subroutine shape_functions_ndim::james_quadrature_quad_tet (l1, l2, l3, l4, normx, normy, normz, sarea, X_LOC, Y_LOC, Z_LOC, CV_NEILOC, cv_nloc, scvngi)
 : the surface quadrature pts in local coord are l1, l2, l3, l4, and the associated normals normx, normy, normz and the surface area is sarea The position of the nodes of the tet are: (X_LOC, Y_LOC, Z_LOC) Calculate cv_neiloc: To get the neighbouring node for node ILOC and surface quadrature point SGI CV_JLOC = CV_NEILOC( CV_ILOC, SGI ) The number of quadrature points is 24 = 4 x 6 exterior faces (and quadrature points) and 36 = 4x6 + 6x4/2 = 60 pts. @WARNING: Disabled because it introduces errors More...
 
subroutine set_quad (l, area, normal, quad)
 
type(quad_data) function sum_gp (q1, q2, q3)
 
type(quad_data) function quad_gp (i1, i2, i3)
 
type(quad_data) function quad4_gp (i1, i2, i3, i4)
 
type(quad_data) function quad6_gp (i1, i2, i3, i4, i5, i6)
 
real function, dimension(3) cross4 (v1, v2)
 
real function triangle_area (v1, v2)
 
subroutine set_neiloc_tet (neighbour_list, vertices)
 
subroutine shape_functions_ndim::get_tang_binorm (NX, NY, NZ, T1X, T1Y, T1Z, T2X, T2Y, T2Z, NNODRO)
 
subroutine shape_functions_ndim::compute_surfaceshapefunctions_triangle_tetrahedron (cv_nloc_cells, cv_ele_type_cells, cv_ele_type, ndim, totele, cv_nloc, scvngi, x_nonods, quad_cv_nloc, x_ndgln, x, y, z, lx, ly, lz, fem_nod, sn, snlx, snly, snlz, sufnlx, sufnly, scvweigh, cv_neiloc_cells, cvfem_neiloc)
 : this subroutine calculates shape functions sn, snlx, snly, snlz, sufnlx, sufnly, their weights scvweigh and local connectivity cv_neiloc_cells, cvfem_neiloc on the boundaries of the cv_nloc_cells control volumes. The control volume types are defines using cv_ele_type_cells. cv_neiloc_cells is associated with the CV cells cvfem_neiloc is associated with the FEM basis SN etc. More...
 
subroutine shape_functions_ndim::dummy_tri_tet (d1, d3, quad_cv_ngi, quad_cv_nloc, dummy_sngi, dummy_snloc, nwicel, cv_nloc, cv_sngi, totele, quad_u_loc_dummy, mloc, dummy_smloc, lowqua, npoly, npoly_ngi)
 Compute some local variables for suf_shape_tri_tet. More...
 
subroutine shape_functions_ndim::shape_tri_tet (cv_ele_type_cells, cv_nloc_cells, cv_ele_type, ndim, totele, cv_nloc, cv_ngi, x_nonods, quad_cv_nloc, x_ndgln, x, y, z, lx, ly, lz, n, nlx, nly, nlz, cvweigh)
 : Determine the volume shape functions n, nlx, nly, nlz and weights cvweigh for the cv_nloc_cells CV cells. More...
 
subroutine shape_functions_ndim::shatri_hex (l1, l2, l3, l4, weight, d3, nloc, ngi, n, nlx, nly, nlz, tri_tet)
 Get the shape functions on lines (in 2D) and quadrilateral surfaces in 3D. More...
 
subroutine shape_functions_ndim::shatri (l1, l2, l3, l4, weight, d3, nloc, ngi, n, nlx, nly, nlz)
 get the shape functions for a triangle/tetrahedron More...
 
subroutine shape_functions_ndim::shape_triangle_cubic (l1, l2, l3, l4, weight, d3, nloc, ngi, n, nlx, nly, nlz)
 Generates the shape functions of a cubic triangle. More...
 
subroutine shape_functions_ndim::base_order_tri (n, nloc, ngi)
 order so that the 1st nodes are on the base for a quadratic triangle... More...
 
subroutine shape_functions_ndim::base_order_tet (n, nloc, ngi)
 order so that the 1st nodes are on the base of tet for a quadratic tet... More...
 
subroutine shape_functions_ndim::calc_cvn_tritetquadhex (cv_ele_type, totele, cv_nloc, cv_ngi, x_nonods, quad_cv_nloc, x_ndgln, fem_nod, cvn)
 Compute CVN (CV basis function) for triangles, tetrahedra, quadrilaterals and hexahedra. More...
 
subroutine shape_functions_ndim::shape_l_q_quad (lowqua, ngi, nloc, mloc, sngi, snloc, smloc, m, mlx, mly, mlz, weight, n, nlx, nly, nlz, sweigh, sn, snlx, snly, sm, smlx, smly, nwicel, d3)
 This subrt computes shape functions. For now, let's just define for one element type. NB: N may overwrite M if we are not solving for pressure. More...
 
real function shape_functions_ndim::volume_quad_map (cv_iloc, xgi, ygi, zgi, lx, ly, lz)
 Compute the cv_iloc^{th} shape function value at point (xgi, ygi, zgi) More...
 
real function shape_functions_ndim::area_quad_map (cv_iloc, xgi, ygi, lx, ly)
 
real function shape_functions_ndim::tet_vol (a, b, c, d)
 
real function shape_functions_ndim::triareaf (x1, y1, x2, y2, x3, y3)
 
real function shape_functions_ndim::triareaf_sign (x1, y1, x2, y2, x3, y3)
 
subroutine shape_functions_ndim::crossproduct (n, cp, a, b)
 
subroutine shape_functions_ndim::printoutfunmat (n, m, a)
 
subroutine shape_functions_ndim::dgsdetnxloc2 (SNLOC, SNGI, XSL, YSL, ZSL, SN, SNLX, SNLY, SWEIGH, SDETWE, SAREA, D1, D3, DCYL, NORMXN, NORMYN, NORMZN, NORMX, NORMY, NORMZ)
 
subroutine shape_functions_ndim::dgsdetnxloc2_all (SNLOC, SNGI, NDIM, XSL_ALL, SN, SNLX, SNLY, SWEIGH, SDETWE, SAREA, NORMXN_ALL, NORMX_ALL)
 
subroutine shape_functions_ndim::normgi (NORMXN, NORMYN, NORMZN, DXDLX, DYDLX, DZDLX, DXDLY, DYDLY, DZDLY, NORMX, NORMY, NORMZ)
 Calculate the normal at the Gauss pts Perform x-product. N=T1 x T2. More...
 
subroutine shape_functions_ndim::xprod1 (AX, AY, AZ, BX, BY, BZ, CX, CY, CZ)
 Perform the cross product of two vectors. More...
 
subroutine shape_functions_ndim::xprod2 (A, B, C)
 Perform the cross product of two vectors. More...
 
subroutine shape_functions_ndim::make_qtri (totele, x_nloc, max_x_nonods, x_nonods, x_ndgln, lx, ly, x, y, fem_nod)
 
subroutine shape_functions_ndim::computing_small_qtriangles (ele_big, x_nloc_big, totele_big, x_nonods_big, increment_ele_big, x_ndgln_big, x_big, y_big)
 
subroutine shape_functions_ndim::remaping_fields_qtriangles (ele_big, x_nloc_big, totele_big, x_nonods_big, x_ndgln_big, x_big, y_big, x_nonods, x_nloc, totele, x_ndgln, ele_ref, x, y)
 
subroutine shape_functions_ndim::eliminating_repetitive_nodes (totele, x_nloc, x_nonods, over_all, x_ndgln, x, y)
 
subroutine shape_functions_ndim::eliminating_repetitive_nodes_all (totele, x_nloc, x_nonods, mx_x_nonods, x_ndgln, x, y, z)
 
subroutine shape_functions_ndim::adding_extra_parametric_nodes (totele, x_nloc, mx_x_nonods, x_ndgln, x, y)
 
subroutine shape_functions_ndim::make_qtets (totele, quad_cv_nloc, x_nloc, max_x_nonods, x_nonods, x_ndgln_real, lx, ly, lz, x, y, z, fem_nod, xp2, yp2, zp2, x_ndgln_p2)
 This subrt creates the local coordinates and node points for: (a) quadratic tetrahedra of unit volume and (b) 27 points of the 8 hexahedra within the 8 linear tetrahedra. FEM_NOD is the local numbering of the FEM representation of the unit volume quadratic tetrahedron. More...
 
subroutine shape_functions_ndim::make_linear_tetrahedron (ele, quad_cv_nloc, x_nloc, x_nonods, number_of_hexs, xp2, yp2, zp2, x, y, z, x_ndgln_p2, x_ndgln)
 
subroutine shape_functions_ndim::make_bilinear_hexahedra (totele, number_of_hexs, quad_cv_nloc, x_nonods, x, y, z, x_ndgln)
 
subroutine shape_functions_ndim::adding_parametric_nodes_hex (ele, ele_hex, totele, number_of_hexs, quad_cv_nloc, x_nonods, x, y, z, x_ndgln)
 
subroutine shape_functions_ndim::shape_one_ele2 (ndim, cv_ele_type, cv_ngi, cv_nloc, u_nloc, cvweight, cvfen, cvfenlx, cvfenly, cvfenlz, ufen, ufenlx, ufenly, ufenlz, sbcvngi, sbcvfen, sbcvfenslx, sbcvfensly, sbcvfeweigh, sbufen, sbufenslx, sbufensly, nface, cv_sloclist, u_sloclist, cv_snloc, u_snloc)
 : This subrt defines the sub-control volume and FEM shape functions. Shape functions associated with volume integration using both CV basis functions CVN as well as FEM basis functions CVFEN (and its derivatives CVFENLX, CVFENLY, CVFENLZ) More...
 
subroutine shape_functions_ndim::shape (LOWQUA, NGI, NLOC, MLOC, SNGI, SNLOC, SMLOC, M, MLX, MLY, MLZ, WEIGHT, N, NLX, NLY, NLZ, SWEIGH, SN, SNLX, SNLY, SM, SMLX, SMLY, NWICEL, D3)
 
subroutine shape_functions_ndim::tr2or3dqu (NGI, NLOC, MLOC, M, MLX, MLY, MLZ, WEIGHT, N, NLX, NLY, NLZ, SNGI, SNLOC, SWEIGH, SN, SNLX, SNLY, SMLOC, SM, SMLX, SMLY, D3)
 :This subroutine defines the shape functions M and N and their derivatives at the Gauss points for quadratic elements. For 3-D FLOW. More...
 
subroutine shape_functions_ndim::tr2d (LOWQUA, NGI, NLOC, MLOC, M, WEIGHT, N, NLX, NLY, SNGI, SNLOC, SWEIGH, SN, SNLX)
 This subroutine defines the shape functions M and N and their derivatives at the Gauss points For 3-D FLOW. More...
 
subroutine shape_functions_ndim::shatrinew (L1, L2, L3, L4, WEIGHT, NLOC, NGI, N, NLX_ALL)
 : Work out the shape functions and their derivatives... More...
 
subroutine shape_functions_ndim::shatriold (L1, L2, L3, L4, WEIGHT, D3, NLOC, NGI, N, NLX, NLY, NLZ)
 : Work out the shape functions and their derivatives... More...
 
subroutine shape_functions_ndim::triquaold (L1, L2, L3, L4, WEIGHT, D3, NGI)
 : This sub calculates the local corrds L1, L2, L3, L4 and weights at the quadrature points. If D3 it does this for 3Dtetrahedra elements else triangular elements. More...
 
subroutine shape_functions_ndim::spectr (NGI, NLOC, MLOC, M, WEIGHT, N, NLX, NLY, NLZ, D3, D2, IPOLY, IQADRA)
 This subroutine defines a spectal element. IPOLY defines the element type and IQADRA the quadrature. In 2-D the spectral local node numbering is as.. 7 8 9 4 5 6 1 2 3 For 3-D... lz=-1 3 4 1 2 and for lz=1 7 8 5 6. More...
 
subroutine shape_functions_ndim::gtroot (IPOLY, IQADRA, WEIT, NODPOS, QUAPOS, NDGI, NDNOD)
 This sub returns the weights WEIT the quadrature points QUAPOS and the node points NODPOS. NODAL POISTIONS ****** NB if GETNDP then find the nodal positions. More...
 
real function shape_functions_ndim::specfu (DIFF, LXGP, INOD, NDNOD, IPOLY, NODPOS)
 INOD contains the node at which the polynomial is associated with LXGP is the position at which the polynomial is to be avaluated.\ If(DIFF) then find the D poly/DX. More...
 
subroutine shape_functions_ndim::cherot (WEIT, QUAPOS, NDGI, GETNDP)
 This computes the weight and points for Chebyshev-Gauss-Lobatto quadrature. See page 67 of:Spectral Methods in Fluid Dynamics, C.Canuto IF(GETNDP) then get the POSITION OF THE NODES AND DONT BOTHER WITH THE WEITS. More...
 
subroutine shape_functions_ndim::legrot (WEIT, QUAPOS, NDGI, GETNDP)
 This computes the weight and points for Chebyshev-Gauss-Lobatto quadrature. See page 69 of:Spectral Methods in Fluid Dynamics, C.Canuto IF(GETNDP) then get the POSITION OF THE NODES AND DONT BOTHER WITH THE WEITS. More...
 
real function shape_functions_ndim::plegen (LX, K)
 
real function shape_functions_ndim::binomial_coefficient (K, L)
 Calculate binomial coefficients. More...
 
subroutine shape_functions_ndim::lroots (QUAPOS, NDGI)
 This sub works out the Gauss-Lobatto-Legendre roots. More...
 
real function shape_functions_ndim::cheby1 (DIFF, LX, INOD, NDNOD, NODPOS)
 If DIFF then returns the spectral function DIFFERENTIATED W.R.T X associated. This function returns the spectral function associated with node INOD at POINT LX NDNOD=no of nodes in 1-D. NDGI=no of Gauss pts in 1-D. NB The nodes are at the points COS(pie*J/2.) j=0,..,ndgi-1. More...
 
real function shape_functions_ndim::cheby2 (DIFF, LX, INOD, NDNOD, NODPOS)
 If DIFF then returns the spectral function DIFFERENTIATED W.R.T X associated. This function returns the spectral function associated with node INOD at POINT LX NDNOD=no of nodes in 1-D. NDGI=no of Gauss pts in 1-D. NB The nodes are at the points COS(pie*J/2.) j=0,..,ndgi-1. More...
 
real function shape_functions_ndim::tcheb (N, XPT, DIFF, DIFF2)
 If DIFF then return the n'th Chebyshef polynomial differentiated w.r.t x. If DIFF2 then form the 2'nd derivative. This sub returns the value of the K'th Chebyshef polynomial at a point XPT. More...
 
recursive integer function shape_functions_ndim::factorial (n)
 Calculate n! More...
 
real function shape_functions_ndim::legend (DIFF, LX, INOD, NDNOD, NODPOS)
 If DIFF then returns the spectral function DIFFERENTIATED W.R.T X associated. This function returns the spectral function associated with node INOD at POINT LX NDNOD=no of nodes in 1-D. NDGI=no of Gauss pts in 1-D. NB The nodes are at the points COS(pie*J/2.) j=0,..,ndgi-1. More...
 
subroutine shape_functions_ndim::determin_sloclist (CV_SLOCLIST, CV_NLOC, CV_SNLOC, NFACE, ndim, cv_ele_type)
 determine CV_SLOCLIST More...
 
subroutine shape_functions_ndim::jacobl (N, ALPHA, BETA, XJAC)
 COMPUTES THE GAUSS-LOBATTO COLLOCATION POINTS FOR JACOBI POLYNOMIALS. More...
 
subroutine shape_functions_ndim::jacobf (N, POLY, PDER, POLYM1, PDERM1, POLYM2, PDERM2, X)
 COMPUTES THE JACOBI POLYNOMIAL (POLY) AND ITS DERIVATIVE (PDER) OF DEGREE N AT X. More...
 
real function shape_functions_ndim::volume_tethex (hexs, x1, x2, x3, x4, y1, y2, y3, y4, z1, z2, z3, z4)
 
subroutine shape_functions_ndim::get_cvn_compact_overlapping (cv_ele_type, ndim, cv_ngi, cv_nloc, cvn, cvweigh)
 : Calculates the CVN and CVWEIGH shape functions This subroutine is specially created to be used with compact_overlapping More...
 
integer function shape_functions_ndim::get_nwicel (d3, nloc)
 : Provides a number defining the type of element we are dealing with 4,5 Linear tetrahedra, 10 quadratic tetrahedra; 3,4 Linear triangle, 5 quadratic triangle More...
 

Variables

logical shape_functions_linear_quadratic::new_high_order_vol_quadratic_ele_quadrature = .false.
 
logical shape_functions_linear_quadratic::new_quadratic_ele_quadrature = .false.
 

Function/Subroutine Documentation

◆ cross4()

real function, dimension(3) james_quadrature_quad_tet::cross4 ( real, dimension(4), intent(in)  v1,
real, dimension(4), intent(in)  v2 
)
Here is the caller graph for this function:

◆ quad4_gp()

type(quad_data) function james_quadrature_quad_tet::quad4_gp ( integer, intent(in)  i1,
integer, intent(in)  i2,
integer, intent(in)  i3,
integer, intent(in)  i4 
)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ quad6_gp()

type(quad_data) function james_quadrature_quad_tet::quad6_gp ( integer, intent(in)  i1,
integer, intent(in)  i2,
integer, intent(in)  i3,
integer, intent(in)  i4,
integer, intent(in)  i5,
integer, intent(in)  i6 
)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ quad_gp()

type(quad_data) function james_quadrature_quad_tet::quad_gp ( integer, intent(in)  i1,
integer, intent(in)  i2,
integer, intent(in)  i3 
)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ set_neiloc_tet()

subroutine james_quadrature_quad_tet::set_neiloc_tet ( integer, dimension(:,:), intent(inout)  neighbour_list,
integer, dimension(4), intent(in)  vertices 
)
Here is the caller graph for this function:

◆ set_quad()

subroutine james_quadrature_quad_tet::set_quad ( real, dimension(:), intent(out)  l,
real, intent(out)  area,
real, dimension(:), intent(out)  normal,
type(quad_data), intent(in)  quad 
)
Here is the caller graph for this function:

◆ sum_gp()

type(quad_data) function james_quadrature_quad_tet::sum_gp ( type(quad_data), intent(in)  q1,
type(quad_data), intent(in)  q2,
type(quad_data), intent(in)  q3 
)
Here is the caller graph for this function:

◆ triangle_area()

real function james_quadrature_quad_tet::triangle_area ( real, dimension(4), intent(in)  v1,
real, dimension(4), intent(in)  v2 
)
Here is the call graph for this function:
Here is the caller graph for this function: