integer::spldirkind=0!< -1 outside (return -1) no dist to calculate; 0 boundary calculate dist with linked boundaries; 1 inside (return 1) no dist to calculate
integer::spltotkind=0!< -1 outside (return -1) no dist to calculate; 0 boundary calculate dist with linked boundaries; 1 inside (return 1) no dist to calculate
integer::linkedboundaries(2)=0!< stores the spline curve indices in the spline_domain of the spline boundaries that are the closest and at a distance lower than dist_extent (1)
!< (1) is for dirichlet boundaries
!< (2) is for domain boundaries
integer::leftknot(4)=0!< knots pointer for s1424 in wtot then wdir
real(kind=db)::lguess(2)=-1!< Spline parameter left limit as start guess
real(kind=db)::rguess(2)=-1!< Spline parameter right limit as start guess
real(kind=db),allocatable::slims(:,:)!< Spline parameter limits for boundary i in the cell
real(kind=db),allocatable::blen(:)!< curve length boundary i in the cell
end type cellkind
TYPE spline_boundary
! all curves assume right handedness to set which side of the curve is inside or outside
type(SISLCurve)::curve
Real(kind=db)::Dirichlet_val!< Value for the dirichlet boundary condition created by this boundary
Real(kind=db)::epsge=1.0e-5!< geometric resolution used for calculating distances
Real(kind=db)::epsce=1.0e-9!< value of weight below which it is 0
INTEGER(kind(bd))::type=bd_Dirichletconst!< type of boundary conditions
END TYPE spline_boundary
type spline_domain
integer::nbsplines=0!< number of spline boundaries in the domain
type(spline_boundary),allocatable::boundaries(:)!< List of boundaries in the domain
Real(kind=db)::dist_extent=0.1!< distance used for the merging with the plateau function for the weight
type(cellkind),ALLOCATABLE::cellk(:,:)!< Precomputed parameters at each cell for faster weight computation
type(spline2d),pointer::splrz=>null()!< Pointer to the main spline grid used for the FEM solver
Integer::nb1!< Number of grid points in the 1st dimension
Integer::nb2!< Number of grid points in the 2nd dimension
real(kind=db),ALLOCATABLE::x1(:)!< Grid points in first direction for weight interpolation
real(kind=db),ALLOCATABLE::x2(:)!< Grid points in 2nd direction for weight interpolation
real(kind=db),ALLOCATABLE::dx1(:)!< inverse cell width in first direction for weight interpolation
real(kind=db),ALLOCATABLE::dx2(:)!< inverse cell width in 2nd direction for weight interpolation
! We set the interpolation points such that the spline interpolation of the weight uses the same knots as the spline interpolation of the electric potential