65 character(LEN=16),
dimension(0:FE_TOT_NB) ::
fe_name 71 integer ,
dimension(FE_TOT_NB)::
fe_geo 74 integer ,
dimension(FE_TOT_NB)::
fe_dim 78 integer ,
dimension(FE_MAX_NBDOF,FE_TOT_NB)::
fe_dof_geo = -1
82 integer ,
dimension(FE_MAX_NBDOF,FE_TOT_NB)::
fe_dof_type = -1
112 integer ,
dimension(CELL_MAX_NBVTX,FE_MAX_NBDOF,FE_TOT_NB)::
fe_dof_vtx =-1
121 real(RP),
dimension(CELL_MAX_NBVTX,FE_MAX_NBDOF,FE_TOT_NB)::
fe_dof_bary=0._rp
135 subroutine scal_fe(val, nbDof, x, dim, ft)
136 integer ,
intent(in) :: dim, nbDof, ft
137 real(RP),
dimension(nbDof),
intent(out) :: val
138 real(RP),
dimension(dim) ,
intent(in) :: x
142 &
call quit(
'fe_mod: scal_fe:& 144 if ( .NOT.
associated(
fe_func(ft)%u) ) &
145 &
call quit(
"fe_mod: scal_fe:& 146 & scalar fe function 'FE_FUNC(ft)%u' not defined " )
148 &
call quit(
"fe_mod: scal_fe:& 149 & argument 'nbDof' incorrect" )
150 if (
fe_dim(ft) /= dim ) &
151 &
call quit(
"fe_mod: scal_fe:& 152 & argument 'dim' incorrect")
155 call fe_func(ft)%u( val, nbdof, x, dim)
166 integer ,
intent(in) :: dim, nbDof, ft
167 real(RP),
dimension(dim, nbDof),
intent(out) :: val
168 real(RP),
dimension(dim) ,
intent(in) :: x
172 &
call quit(
"fe_mod: scalGrad_fe:& 174 if ( .NOT.
associated(
fe_func(ft)%grad_u) ) &
175 &
call quit(
"fe_mod: scalGrad_fe:& 176 & gradient fe function 'FE_FUNC(ft)%grad_u' not defined" )
178 &
call quit(
"fe_mod: scalGrad_fe:& 179 & argument 'nbDof' incorrect" )
180 if (
fe_dim(ft) /= dim ) &
181 &
call quit(
"fe_mod: scalGrad_fe:& 182 & argument 'dim' incorrect" )
185 call fe_func(ft)%grad_u( val, nbdof, x, dim)
194 subroutine vect_fe(val, nbDof, x, dim, ft)
195 integer ,
intent(in) :: dim, nbDof, ft
196 real(RP),
dimension(dim,nbDof),
intent(out) :: val
197 real(RP),
dimension(dim) ,
intent(in) :: x
201 &
call quit(
"fe_mod: vect_fe: & 203 if ( .NOT.
associated(
fe_func(ft)%phi) )&
204 &
call quit(
"fe_mod: vect_fe: & 205 & vector fe function ' FE_FUNC(ft)%phi' not defined" )
207 &
call quit(
"fe_mod: vect_fe: & 208 & argument 'nbDof' incorrect" )
209 if (
fe_dim(ft) /= dim ) &
210 &
call quit(
"fe_mod: vect_fe: & 211 & argument 'dim' incorrect" )
214 call fe_func(ft)%phi( val, nbdof, x, dim)
225 integer ,
intent(in) :: dim, nbDof, ft
226 real(RP),
dimension(nbDof),
intent(out) :: val
227 real(RP),
dimension(dim) ,
intent(in) :: x
231 &
call quit(
"fe_mod: vectDiv_fe:& 233 if ( .NOT.
associated(
fe_func(ft)%div_phi) ) &
234 &
call quit(
"fe_mod: vectDiv_fe:& 235 & divergence fe function 'FE_FUNC(ft)%div_phi' not defined" )
237 &
call quit(
"fe_mod: vectDiv_fe:& 238 & argument 'nbDof' incorrect" )
239 if (
fe_dim(ft) /= dim ) &
240 &
call quit(
"fe_mod: vectDiv_fe:& 241 & argument 'dim' incorrect" )
244 call fe_func(ft)%div_phi( val, nbdof, x, dim)
252 logical,
intent(in) :: b
254 if (b)
write(*,*)
"fe_mod : fe_init" 321 &
call quit(
'fe_mod: def_FE_NBDOF' )
582 fe_dof_geoelmt(1:n, f ) = (/1,2,3,1,1,2,2,3,3,1/)
598 fe_dof_geoelmt(1:n, f ) = (/1,2,3,4,1,2,3,4,5,6/)
840 x1 = 0.788675134594813_rp
841 x2 = 0.21132486540518702_rp
871 x1 = 0.5_rp * ( 1.0_rp + 1.0_rp / sqrt(3.0_rp ) )
872 x2 = 0.5_rp * ( 1.0_rp - 1.0_rp / sqrt(3.0_rp ) )
980 integer :: ft, dim, geo
995 integer :: ft, nbDof, dim, dof_nbVtx
996 integer :: ii, dof, geo, vtx
997 real(RP),
dimension(3) :: x
1016 x(1:dim) = x(1:dim) +
fe_dof_bary(ii, dof, ft) * &
subroutine rt0_1d_dual_div_phi(val, n, x, m)
RT0 Dual ref choral/applications/PG_star_1D_poisson/sage/PG2_1D_P1_1.sage.
integer, parameter fe_p1_1d_disc_ortho
integer, parameter fe_rt0_2d
subroutine, public fe_init(b)
initialise FE_XXX arrays
integer, dimension(fe_tot_nb), public fe_dim
Reference cell dimension for each fe method.
type(r_2d), dimension(fe_tot_nb), public fe_dof_coord
DOF node coordinates.
integer, dimension(fe_max_nbdof, fe_tot_nb), public fe_dof_geo
FE_DOF_GEO(i, j) = Geometric type of DOF i of the FE method j.
subroutine rt0_1d_phi(val, n, x, m)
RT0 1D.
integer, parameter cell_tet
Tetrahedron.
DEFINITION OF FINITE ELEMENT BASIS FUNCTIONS
integer, dimension(cell_tot_nb), public cell_nbvtx
Number of vertexes for each cell type.
subroutine p1_3d_u(val, n, x, m)
P1_3d.
integer, parameter fe_p2_2d
subroutine p1_2d_disc_ortho_u(val, n, x, m)
P1_2d_disc_ortho.
subroutine rt1_2d_2_div_phi(val, n, xx, m)
RT1_2D.
subroutine rt1_1d_dual_phi(val, n, x, m)
RT1_1D_DUAL ref = applications/PG_star_1D_poisson/sage/PG2_1D_P2_1.sage.
subroutine rt1_1d_div_phi(val, n, x, m)
RT1_1D, considered with the usual basis for the DOFs: f(0), f(1), f(1/2) ref = applications/PG_star_1...
subroutine rt0_2d_div_phi(val, n, x, m)
RT0 2D.
integer, parameter fe_dof_nrm_trace
Normal component to a face (vector finite element)
subroutine p2_3d_u(val, n, x, m)
P2_3d.
subroutine p1_1d_u(val, n, x, m)
P1_1d.
DEFINITION OF FINITE ELEMENT METHODS
integer, parameter fe_rt1_1d_dual
subroutine p1_1d_disc_ortho_u(val, n, x, m)
P1_1d_disc_ortho.
subroutine p3_2d_grad_u(val, n, x, m)
P3_2d.
subroutine def_fe_dof_geo()
DOF geometrical types.
integer, parameter fe_dof_comp1
Nodal first component (vector finite element)
subroutine rt0_1d_dual_phi(val, n, x, m)
RT0 Dual ref choral/applications/PG_star_1D_poisson/sage/PG2_1D_P1_1.sage.
integer, parameter fe_p1_2d_disc_ortho
subroutine rt1_1d_2_dual_div_phi(val, n, x, m)
RT1_1D_2_DUAL ref = applications/PG_star_1D_poisson/sage/PG2_1D_P2_3.sage.
integer, parameter fe_dof_flx
Interface flux (vector finite element)
integer, parameter fe_rt0_1d_dual
subroutine rt1_2d_2_phi(val, n, xx, m)
RT1_2D.
integer, parameter fe_dof_comp2
Nodal second component (vector finite element)
integer, parameter fe_rt1_2d_2
integer, dimension(fe_max_nbdof, fe_tot_nb), public fe_dof_nbvtx
FE_DOF_NBVTX(i,j) = number of vertexes of the geometric element associated with the DOF i of the FE m...
integer, parameter cell_edg
Edge (line segment)
integer, parameter fe_tot_nb
Number of FE methods.
subroutine p1_1d_grad_u(val, n, x, m)
P1_1d.
integer, dimension(cell_tot_nb), public cell_dim
Dimension for each cell type.
conversion integers or rational to real
integer, parameter fe_max_nbdof
Maximum number of dof for an element.
REAL NUMBERS PRECISION IN CHORAL: selects simple/double/quad
subroutine, public scalgrad_fe(val, nbDof, x, dim, ft)
Evaluate the gradient of the FE basis functions at point x.
integer, parameter fe_p2_3d
subroutine p2_2d_u(val, n, x, m)
P2_2d.
subroutine p0_2d_u(val, n, x, m)
P0_2d.
subroutine def_fe()
Number of DOF for each FE method.
subroutine def_fe_dim()
set FE dimension
subroutine p2_3d_grad_u(val, n, x, m)
P2_3d.
subroutine rt1_1d_phi(val, n, x, m)
RT1_1D, considered with the usual basis for the DOFs: f(0), f(1), f(1/2) ref = applications/PG_star_1...
integer, parameter fe_p3_1d
type(r_2d), dimension(cell_tot_nb), public cell_coord
Cell node coordinates.
subroutine p2_1d_grad_u(val, n, x, m)
P2_1d.
integer, parameter cell_trg
Triangle.
integer, dimension(fe_tot_nb), public fe_nbdof
Number of DOF for each fe method.
subroutine p1_2d_grad_u(val, n, x, m)
P1_2d.
subroutine def_fe_dof_geoelmt()
in the cell K :
subroutine, public vect_fe(val, nbDof, x, dim, ft)
Evaluate vector FE basis functions at point x.
subroutine p0_1d_u(val, n, x, m)
P0_1d.
subroutine def_fe_dof_vtx()
FE_DOF_VTX(1:n, i, f) = vertexes of the ref. cell associated to the dof i of the FE method f...
subroutine p3_2d_u(val, n, x, m)
P3_2d.
type(fe_functions), dimension(fe_tot_nb), public fe_func
FE_ARRAY Arrays describing finite element methods.
subroutine rt1_1d_2_phi(val, n, x, m)
RT1_1D_2, considered with the alternative basis for the DOFs: f(0), f(1), ^1 f(x) dx ref = applicatio...
subroutine p1_2d_u(val, n, x, m)
P1_2d.
integer, parameter fe_p1_2d
subroutine rt0_2d_phi(val, n, x, m)
RT0 2D.
subroutine rt1_1d_2_div_phi(val, n, x, m)
RT1 1D_2, considered with the alternative basis for the DOFs: f(0), f(1), ^1 f(x) dx ref = applicatio...
subroutine p2_2d_grad_u(val, n, x, m)
P2_2d.
integer, parameter fe_rt1_1d_2_dual
integer, dimension(cell_max_nbvtx, fe_max_nbdof, fe_tot_nb), public fe_dof_vtx
FE_DOF_VTX(1:n,i,j) = for the DOF i of the FE method j :
subroutine rt1_1d_2_dual_phi(val, n, x, m)
RT1_1D_2_DUAL ref = applications/PG_star_1D_poisson/sage/PG2_1D_P2_3.sage.
subroutine p1_3d_grad_u(val, n, x, m)
P1_3d.
integer, parameter fe_dof_lag
Nodal value (Lagrangian DOF, scalar finite element)
integer, dimension(fe_tot_nb), public fe_geo
Reference cell geometry for each fe method.
character(len=16), dimension(0:fe_tot_nb), public fe_name
Name for each fe method.
subroutine def_fe_dof_bary()
FE_DOF_BARY(1:n, i, f) = barycentric coordinates of the dof i of the FE method f. ...
integer, parameter fe_rt1_1d
subroutine rt1_1d_dual_div_phi(val, n, x, m)
RT1_1D_DUAL ref = applications/PG_star_1D_poisson/sage/PG2_1D_P2_1.sage.
subroutine def_fe_dof_type()
DOF types.
integer, parameter fe_none
subroutine rt0_1d_div_phi(val, n, x, m)
RT0 1D.
integer, parameter fe_rt1_1d_2
subroutine p2_1d_u(val, n, x, m)
P2_1d.
integer, parameter fe_p0_1d
integer, parameter cell_vtx
Vertex.
integer, dimension(fe_max_nbdof, fe_tot_nb), public fe_dof_geoelmt
For the FE method j : the associated reference cell is := FE_GEO(i)
subroutine def_fe_dof_coord()
set FE dof coordinates
real(rp), dimension(cell_max_nbvtx, fe_max_nbdof, fe_tot_nb), public fe_dof_bary
FE_DOF_BARY(1:n,i,j) = for the DOF i of the FE method j :
integer, parameter fe_p3_2d
subroutine, public vectdiv_fe(val, nbDof, x, dim, ft)
Evaluate the divergence of the vector FE basis functions at point x.
R_2D: this type will allow to define arrays of 2D real arrays.
integer, parameter fe_p0_2d
integer, dimension(fe_max_nbdof, fe_tot_nb), public fe_dof_type
FE_DOF_TYPE(i,j) = dof type of the DOF i of the FE method j (Lagrange, ...)
integer, parameter fe_p1_3d
integer, parameter fe_p1_1d
Functions associated with a finite element.
subroutine def_fe_func()
Finite element function.
DEFINITION OF GEOMETRICAL CELLS (for meshes)
subroutine p3_1d_u(val, n, x, m)
P3_1d.
subroutine def_fe_dof_nbvtx()
FE DOF number of vertexes.
integer, parameter fe_rt0_1d
integer, parameter fe_p2_1d
subroutine, public scal_fe(val, nbDof, x, dim, ft)
Evaluate FE basis functions at point x.
subroutine p3_1d_grad_u(val, n, x, m)
P3_1d.