VS2.1 - Illustration of PCDs in One Triangle

Elvan Ceyhan

2023-12-18

First we load the pcds package:

library(pcds)

2 Functions for PCDs with Vertices in One Triangle

Due to geometry invariance of PE- and CS-PCDs for uniform data (which will be the vertices of the PCDs) in any triangle in 2D space, most computations (and if needed data generation and simulations) can be done in the standard equilateral triangle, and for AS-PCD, one can restrict attention to the standard basic triangle. The standard equilateral triangle is \(T_e=T(A,B,C)\) with vertices \(A=(0,0)\), \(B=(1,0)\), and \(C=(1/2,\sqrt{3}/2)\) and the standard basic triangle is \(T_b=T(A,B,C')\) with vertices \(A=(0,0)\), \(B=(1,0)\), and \(C'=(c_1,c_2))\) with \(0 < c_1 \le 1/2\), \(c_2>0\), and \((1-c_1)^2+c_2^2 \le 1\).

Most of the PCD functions we will illustrate in this section are counterparts of the functions in Section “VS1_1_2DArtiData” (i.e. one-interval counterparts of the functions for the multiple-triangle setting). Sometimes we will be focusing on the standard equilateral triangle (for speed and ease of computation).

For more detail on the construction and appealing properties of PCDs in triangles, see Ceyhan (2010) and Ceyhan (2012).

We first choose an arbitrary triangle \(T=T(A,B,C)\) with vertices \(A=(1,1)\), \(B=(2,0)\), and \(C=(1.5,2)\), which happens to be an obtuse triangle, and choose an arbitrary point in the interior of this triangle as the center (to construct the vertex or edge regions).

A<-c(1,1); B<-c(2,0); C<-c(1.5,2);
Tr<-rbind(A,B,C);
n<-5

set.seed(1)
Xp<-runif.tri(n,Tr)$g  #try also Xp<-cbind(runif(n,1,2),runif(n,0,2))
M<-c(1.6,1.2) #try also M<-as.numeric(runif.tri(1,Tr)$g) or M="CC"

Then we generate \(n=\) 5 \(\mathcal{X}\) points inside the triangle \(T\) using the function runif.tri in pcds. \(\mathcal{X}\) points are denoted as Xp and \(\mathcal{Y}\) points in Section “VS1_1_2DArtiData” correspond to the vertices of the triangle \(T\). Hence, if the argument Yp is used for a function for multiple triangles, it is replaced with tri a \(3 \times 2\) matrix in which rows represent the vertices of the triangle for a function written for a general triangle, with c1,c2 for a basic triangle, or omitted for the standard equilateral triangle.

We plot the triangle \(T\) and the \(\mathcal{X}\) points in it using the below code, and also add the vertex names using the text function from base R.

Xlim<-range(Tr[,1])
Ylim<-range(Tr[,2])
plot(Tr,pch=".",xlab="",ylab="",xlim=Xlim,ylim=Ylim+c(0,.1),main="Points in One Triangle")
polygon(Tr)
points(Xp)

#add the vertex names and annotation
txt<-rbind(Tr)
xc<-txt[,1]+c(-.01,.015,.02)
yc<-txt[,2]+c(.02,.02,.02)
txt.str<-c("A","B","C")
text(xc,yc,txt.str)

Alternatively, we can use the plotDelaunay.tri function in pcds to obtain the same plot by executing plotDelaunay.tri(Xp,Tr,xlab="x",ylab="y").

2.1 Functions for Arc-Slice PCDs with Vertices in One Triangle

Arc-Slice (AS) proximity region for a point is the intersection of the triangle containing the point and the circle centered the point with radius being the minimum distance from the point to the vertices of the triangle. So, we first check whether a point is inside a circle or not by using the function in.circle which returns TRUE if the point is inside the circle, and FALSE otherwise. This function takes arguments p,cent,rad,boundary where

cent<-c(1,1); rad<-1; p<-c(1.4,1.2) #try also cent<-runif(2); rad<-runif(1); p<-runif(2);
in.circle(p,cent,rad)
p<-c(.4,-.2)
in.circle(p,cent,rad)

#> [1] TRUE
#> [1] FALSE

The circle for an AS proximity region of an \(\mathcal{X}\) point \(x\) is centered at the point \(x\) with radius being the distance from \(x\) to the closest class \(\mathcal{Y}\) point (which is the closest vertex of the triangle \(T\) in the one triangle setting). The radius of a point from one class with respect to points from the other class is provided by the function radius which takes arguments p,Y where

The function also returns the index and coordinates of the class \(\mathcal{Y}\) point closest to the class \(\mathcal{X}\) point. This function works for points in other dimensions as well. See ? radius for further description.

ny<-5
Y<-cbind(runif(ny),runif(ny))
A<-c(1,1);
radius(A,Y)
#> $rad
#> [1] 0.3767951
#> 
#> $index.of.clYpnt
#> [1] 4
#> 
#> $closest.Ypnt
#> [1] 0.6684667 0.8209463

The radii of points from one class with respect to points from the other class are found by using the function radii which takes arguments x,y where

In addition to the radii, the function also returns the indices and coordinates of the class \(\mathcal{Y}\) points closest to the class \(\mathcal{X}\) points. This function works for points in other dimensions as well. See ? radii for further description.

nx<-6
ny<-5
X<-cbind(runif(nx),runif(nx))
Y<-cbind(runif(ny),runif(ny))
Rad<-radii(X,Y)
Rad
#> $radiuses
#> [1] 0.38015546 0.23618472 0.02161322 0.48477828 0.05674010 0.16819521
#> 
#> $indices.of.closest.points
#> [1] 4 4 4 4 1 3
#> 
#> $closest.points
#>            [,1]      [,2]
#> [1,] 0.51863426 0.4590657
#> [2,] 0.51863426 0.4590657
#> [3,] 0.51863426 0.4590657
#> [4,] 0.51863426 0.4590657
#> [5,] 0.07067905 0.4068302
#> [6,] 0.31627171 0.2936034

The function NAStri is used for the construction of AS proximity regions taking the arguments

NAStri returns the proximity region as end points of the straight line segments on the boundary of the proximity region (which also fall on the boundary of the triangle), the end points of the arc slices which are the parts of the defining circle falling in the interior of the triangle and the angles between the vectors joining P and the end points of the arc slices and the horizontal line crossing the point P. It is also possible to specify the index of the vertex region for the point P with the argument rv=k for \(k=1,2,3\), where \(k\) refers to the vertex in \(k\)-th row for the triangle Tr (but this must be computed before such as in the code Rv<-rel.vert.triCC(P1,Tr)$rv; NAStri(P1,Tr,M,Rv) and it must be compatible with the vertex region for the point P).

P<-c(1.8,.5)
NAStri(P,Tr,M)
#> $L
#>      [,1] [,2]
#> [1,]    2    0
#> [2,]    2    0
#> 
#> $R
#>          [,1]     [,2]
#> [1,] 1.741176 1.035294
#> [2,] 1.300000 0.700000
#> 
#> $arc.slices
#>          [,1]     [,2]
#> [1,] 1.741176 1.035294
#> [2,] 1.300000 0.700000
#> 
#> $Angles
#> [1] 1.680247 2.761086

Indicator for the presence of an arc from a (data or \(\mathcal{X}\)) point to another for AS-PCDs is the function IarcAStri. One can use it for points in the data set or for arbitrary points (as if they were in the data set). It takes the arguments,

This function returns \(I(p2 \in N_{AS}(p1))\), that is, returns 1 if p2 is in \(N_{AS}(p1)\), 0 otherwise.

#between two arbitrary points P1 and P2
P1<-as.numeric(runif.tri(1,Tr)$g)
P2<-as.numeric(runif.tri(1,Tr)$g)
IarcAStri(P1,P2,Tr,M)
#> [1] 0
#between the first two points in Xp
IarcAStri(Xp[1,],Xp[2,],Tr,M)
#> [1] 0

AS proximity regions are defined with respect to the vertices of the triangle (i.e., with respect to the vertex regions they reside in) and vertex regions in each triangle are based on the center M for circumcenter or \(M=(\alpha,\beta,\gamma)\) in barycentric coordinates in the interior of the triangle; default is M="CC" i.e., circumcenter of the triangle.

See Ceyhan (2005), Ceyhan (2010), and Ceyhan (2012) for more on AS-PCDs.

Number of arcs of the AS-PCD can be computed by the function num.arcsAStri. The function num.arcsAStri is an object of class “NumArcs” and takes Xp,tri,M="CC" as its arguments where Xp is the data set, and the others are as above and returns the list of

Narcs = num.arcsAStri(Xp,Tr)  #with default M="CC"; try also num.arcsAStri(Xp,Tr,M)
summary(Narcs)
#> Call:
#> num.arcsAStri(Xp = Xp, tri = Tr)
#>
#> Description of the output:
#> Number of Arcs of the AS-PCD and the Related Quantities with vertices Xp in One Triangle
#>
#> Number of data (Xp) points in the triangle =  5
#> Number of arcs in the digraph =  10
#>
#> Indices of data points in the triangle:
#> 1 2 3 4 5 
#> 
#plot(Narcs)

The arc density of the AS-PCD can be computed by the function ASarc.dens.tri. It takes the arguments Xp,tri,M="CC",in.tri.only where Xp is the data set (or \(\mathcal{X}\) points) tri,M="CC" are as above. in.tri.only is a logical argument (default is FALSE) for considering only the points inside the triangle or all the points as the vertices of the digraph. if in.tri.only=TRUE, arc density is computed only for the points inside the triangle (i.e., arc density of the subdigraph induced by the vertices in the triangle is computed), otherwise arc density of the entire digraph (i.e., digraph with all the vertices) is computed.

ASarc.dens.tri(Xp,Tr,M)
#> [1] 0.5

The incidence matrix of the AS-PCD for the one triangle case can be found by inci.matAStri, using the inci.matAStri(Xp,Tr,M) command. It takes the same arguments as the function num.arcsAStri.

Plot of the arcs in the digraph AS-PCD, which is based on the \(M\)-vertex regions with \(M=(\) 1.6,1.2 \()\), can be obtained by the function plotASarcs.tri, which is the one-tri counterpart of the function plotASarcs. It takes arguments Xp,tri,M="CC" (as in num.arcsAStri) and other options for the plot function. See the help page for the function using ? plotASarcs.tri.

Plot of the arcs of the above AS-PCD, together with the vertex regions (with the option vert.reg = TRUE).

plotASarcs.tri(Xp,Tr,M,xlab="",ylab="",vert.reg = TRUE)
Arcs of the AS-PCD with 10 $X$ points, vertex regions are added with dashed lines.

Figure 2.1: Arcs of the AS-PCD with 10 \(X\) points, vertex regions are added with dashed lines.

Or, one can use the default center M="CC", and can add vertex names and text to the figure (with vertex regions) using the below code. The part M = as.numeric(arcsAStri(Xp,Tr)$param) is optional, for the below annotation of the plot since circumcenter is used for the vertex regions.

oldpar <- par(pty = "s")
plotASarcs.tri(Xp,Tr,asp=1,xlab="",ylab="",vert.reg = TRUE); M = (arcsAStri(Xp,Tr)$param)$c

CC<-circumcenter.tri(Tr)

#determine whether the center used for vertex regions is circumcenter or not
if (identical(M,CC) || identical(M,"CC"))
{cent<-CC
D1<-(B+C)/2; D2<-(A+C)/2; D3<-(A+B)/2;
Ds<-rbind(D1,D2,D3)
cent.name<-"CC"
} else
{cent<-M
cent.name<-"M"
Ds<-prj.cent2edges(Tr,M)
}

#add the vertex names and annotation
txt<-rbind(Tr,cent,Ds)
xc<-txt[,1]+c(-.02,.02,.02,.05,.05,-0.03,-.01)
yc<-txt[,2]+c(.02,.02,.02,.07,.02,.05,-.06)
txt.str<-c("A","B","C",cent.name,"D1","D2","D3")
text(xc,yc,txt.str)
par(oldpar)

Plot of the AS proximity regions can be obtained by the function plotASregs.tri. It takes arguments Xp,tri,M="CC" (as in num.arcsAStri) and other options for the plot function. See the help page for the function using ? plotASregs.tri.

M<-c(1.6,1.2) #try also M<-c(1.6620051,0.8136604) or M="CC"
oldpar <- par(pty = "s")
plotASregs.tri(Xp,Tr,M,vert.reg = T,xlab="",ylab="")
AS proximity regions for the $X$ points used above.

Figure 2.2: AS proximity regions for the \(X\) points used above.

par(oldpar)

The function arcsAStri is an object of class “PCDs”. It takes arguments Xp,tri,M="CC" (as in ASarc.dens.tri). The output list is as in the function arcsAS (see Section “VS1_1_2DArtiData”). The plot function returns the same plot as in plotASarcs.tri with \(M=(\) 1.6,1.2 \()\), hence we comment it out below.

M=c(1.6,1.2) #try also M=c(1.6620051,0.8136604)

Arcs<-arcsAStri(Xp,Tr,M) #try also Arcs<-arcsAStri(Xp,Tr) #uses the default center, namely circumcenter for M
Arcs
#> Call:
#> arcsAStri(Xp = Xp, tri = Tr, M = M)
#> 
#> Type:
#> [1] "Arc Slice Proximity Catch Digraph (AS-PCD) for 2D Points in the Triangle with Center M = (1.6,1.2)"
summary(Arcs)
#> Call:
#> arcsAStri(Xp = Xp, tri = Tr, M = M)
#> 
#> Type of the digraph:
#> [1] "Arc Slice Proximity Catch Digraph (AS-PCD) for 2D Points in the Triangle with Center M = (1.6,1.2)"
#> 
#>  Vertices of the digraph =  Xp 
#>  Partition points of the region =  Tr 
#> 
#>  Selected tail (or source) points of the arcs in the digraph
#>       (first 6 or fewer are printed) 
#>          [,1]      [,2]
#> [1,] 1.265509 0.7442478
#> [2,] 1.687023 0.7682074
#> [3,] 1.687023 0.7682074
#> [4,] 1.687023 0.7682074
#> [5,] 1.380035 1.5548904
#> [6,] 1.267221 0.7722282
#> 
#>  Selected head (or end) points of the arcs in the digraph
#>       (first 6 or fewer are printed) 
#>          [,1]      [,2]
#> [1,] 1.267221 0.7722282
#> [2,] 1.265509 0.7442478
#> [3,] 1.267221 0.7722282
#> [4,] 1.482080 1.1991317
#> [5,] 1.482080 1.1991317
#> [6,] 1.265509 0.7442478
#> 
#> Parameters of the digraph
#> $center
#> [1] 1.6 1.2
#> 
#> Various quantities of the digraph
#>         number of vertices number of partition points 
#>                        5.0                        3.0 
#>        number of triangles             number of arcs 
#>                        1.0                       10.0 
#>                arc density 
#>                        0.5

plot(Arcs)

To see the code and the plot for the arcs using the plot.PCDs function, with vertex names and annotation added to the plot, type ? arcsAStri.

2.2 Functions for Proportional Edge PCDs with Vertices in One Triangle

In this section, we use the same triangle \(T\) and generate data as in Section 2.1.

#A<-c(1,1); B<-c(2,0); C<-c(1.5,2); Tr<-rbind(A,B,C); n<-5
#set.seed(1); Xp<-runif.tri(n,Tr)$g
M<-c(1.6,1.0)  #try also M<-as.numeric(runif.tri(1,Tr)$g)
r<-1.5  #try also r<-2

And choose the expansion parameter \(r=\) 1.5 to illustrate proportional edge (PE) proximity regions and the associated PCDs.

The function NPEtri is used for the construction of PE proximity regions taking the arguments p,tri,r,M=c(1,1,1),rv=NULL where

NPEtri returns the PE proximity region (i.e., the vertices of the triangular proximity region).

P<-c(1.8,.5)
NPEtri(P,Tr,r,M)
#>       [,1] [,2]
#> [1,] 2.000 0.00
#> [2,] 1.550 0.45
#> [3,] 1.775 0.90

Indicator for the presence of an arc from a (data or \(\mathcal{X}\)) point to another for PE-PCDs is the function IarcPEtri. One can use it for points in the data set or for arbitrary points (as if they were in the data set). It takes the arguments, p1,p2,tri,r,M=c(1,1,1),rv=NULL where

-p1,p2,tri,rv=NULL are as in IarcAStri and - r,M=c(1,1,1) are as in NPEtri.

This function returns \(I(p2 \in N_{PE}(p1))\), that is, returns 1 if p2 is in \(N_{PE}(p1)\), 0 otherwise.

P1<-as.numeric(runif.tri(1,Tr)$g)
P2<-as.numeric(runif.tri(1,Tr)$g)
IarcPEtri(P1,P2,Tr,r,M)
#> [1] 1
IarcPEtri(Xp[1,],Xp[5,],Tr,r,M) #try also IarcPEtri(Xp[5,],Xp[1,],Tr,r,M)
#> [1] 0

Number of arcs of the PE-PCD can be computed by the function num.arcsPEtri, which is an object of class “NumArcs” and takes arguments Xp,tri,r,M=c(1,1,1) where Xp is the data set, and the others are as above. The output is as in num.arcsAStri.

Narcs = num.arcsPEtri(Xp,Tr,r,M)
summary(Narcs)
#> Call:
#> num.arcsPEtri(Xp = Xp, tri = Tr, r = r, M = M)
#>
#> Description of the output:
#> Number of Arcs of the PE-PCD with vertices Xp and Quantities Related to the Support Triangle
#>
#> Number of data (Xp) points in the triangle =  5
#> Number of arcs in the digraph =  7
#>
#> Indices of data points in the triangle:
#> 1 2 3 4 5 
#> 
#plot(Narcs)

The arc density of the PE-PCD can be computed by the function PEarc.dens.tri. It takes the arguments Xp,tri,r,M,in.tri.only where Xp is the data set (or \(\mathcal{X}\) points) r,tri,M are as above, in.tri.only is as in ASarc.dens.tri, and returns output as list with elements

The standardized arc density is only correct when \(M\) is the center of mass in the current version.

PEarc.dens.tri(Xp,Tr,r,M)
#> $arc.dens
#> [1] 0.35

The incidence matrix of the PE-PCD for the one triangle case can be found by the function inci.matPEtri, using e.g. the inci.matPEtri(Xp,Tr,r,M) command. It takes the same arguments as the function num.arcsPEtri.

Plot of the arcs in the digraph PE-PCD, which is based on the \(M\)-vertex regions with \(M=\)(1.6,1), can be obtained by the function plotPEarcs.tri, which is the one-tri counterpart of the function plotPEarcs. It takes arguments Xp,tri,r,M=c(1,1,1) (as in num.arcsPEtri) and other options for the plot function. See the help page for the function using ? plotPEarcs.tri.

Plot of the arcs of the above PE-PCD, together with the vertex regions (with the option vert.reg = TRUE) and vertex names added to the figure.

plotPEarcs.tri(Xp,Tr,r,M,xlab="",ylab="",vert.reg = TRUE)
#add vertex labels and text to the figure (with vertex regions)
ifelse(isTRUE(all.equal(M,circumcenter.tri(Tr))),
       {Ds<-rbind((B+C)/2,(A+C)/2,(A+B)/2); cent.name="CC"},{Ds<-prj.cent2edges(Tr,M); cent.name="M"})
#> [1] "M"

txt<-rbind(Tr,M,Ds)
xc<-txt[,1]+c(-.02,.02,.02,.02,.04,-0.03,-.01)
yc<-txt[,2]+c(.02,.02,.02,.05,.02,.04,-.06)
txt.str<-c("A","B","C",cent.name,"D1","D2","D3")
text(xc,yc,txt.str)
Arcs of the PE-PCD with 10 $X$ points and vertex regions (dashed lines) are based on $M$. The vertices and the center are labeled.

Figure 2.3: Arcs of the PE-PCD with 10 \(X\) points and vertex regions (dashed lines) are based on \(M\). The vertices and the center are labeled.

Plots of the PE proximity regions can be obtained by the function plotPEregs.tri. It takes arguments Xp,tri,r,M=c(1,1,1) (as in num.arcsPEtri) and other options for the plot function. See the help page for the function using ? plotPEregs.tri.

M<-c(1.6,1.2) #try also M<-c(1.6620051,0.8136604) or M="CC"
plotPEregs.tri(Xp,Tr,r,M,vert.reg = T,xlab="",ylab="")
PE proximity regions for the $X$ points used above.

Figure 2.4: PE proximity regions for the \(X\) points used above.

The function ArcsPEtri is an object of class “PCDs”. It takes arguments Xp,tri,r,M=c(1,1,1) (as in num.arcsPEtri). The output list is as in the arcsAStri except the parameters of the digraph (center for PE-PCD and the expansion parameter). The plot function returns the same plot as in plotPEarcs.tri, hence we comment it out below.

Arcs<-ArcsPEtri(Xp,Tr,r,M) #or try with the default center Arcs<-ArcsPEtri(Xp,Tr,r); M= (Arcs$param)$cent
Arcs
#> Call:
#> ArcsPEtri(Xp = Xp, tri = Tr, r = r, M = M)
#> 
#> Type:
#> [1] "Proportional Edge Proximity Catch Digraph (PE-PCD) for 2D Points in the Triangle with Expansion Parameter r = 1.5 and Center M = (1.6,1.2)"
summary(Arcs)
#> Call:
#> ArcsPEtri(Xp = Xp, tri = Tr, r = r, M = M)
#> 
#> Type of the digraph:
#> [1] "Proportional Edge Proximity Catch Digraph (PE-PCD) for 2D Points in the Triangle with Expansion Parameter r = 1.5 and Center M = (1.6,1.2)"
#> 
#>  Vertices of the digraph =  Xp 
#>  Partition points of the region =  Tr 
#> 
#>  Selected tail (or source) points of the arcs in the digraph
#>       (first 6 or fewer are printed) 
#>          [,1]      [,2]
#> [1,] 1.265509 0.7442478
#> [2,] 1.380035 1.5548904
#> [3,] 1.380035 1.5548904
#> [4,] 1.380035 1.5548904
#> [5,] 1.380035 1.5548904
#> [6,] 1.267221 0.7722282
#> 
#>  Selected head (or end) points of the arcs in the digraph
#>       (first 6 or fewer are printed) 
#>          [,1]      [,2]
#> [1,] 1.267221 0.7722282
#> [2,] 1.265509 0.7442478
#> [3,] 1.687023 0.7682074
#> [4,] 1.267221 0.7722282
#> [5,] 1.482080 1.1991317
#> [6,] 1.265509 0.7442478
#> 
#> Parameters of the digraph
#> $center
#> [1] 1.6 1.2
#> 
#> $`expansion parameter`
#> [1] 1.5
#> 
#> Various quantities of the digraph
#>         number of vertices number of partition points 
#>                        5.0                        3.0 
#>        number of triangles             number of arcs 
#>                        1.0                       10.0 
#>                arc density 
#>                        0.5

plot(Arcs)

To see the code and the plot for the arcs using the plot.PCDs function, with vertex names and annotation added to the plot, type ? ArcsPEtri.

2.3 Functions for Central Similarity PCDs with Vertices in One Triangle

We use the same triangle \(T\) and generated data as Section 2.2.

tau<-1.5

And choose the expansion parameter \(\tau=\) 1.5 to illustrate central similarity proximity regions and the associated PCDs.

The function NCStri is used for the construction of CS proximity regions taking the arguments p,tri,t,M=c(1,1,1),re=NULL where

NCStri returns the CS proximity region (i.e., the vertices of the triangular proximity region).

P<-c(1.8,.5)
NCStri(P,Tr,tau,M)
#>         [,1]   [,2]
#> [1,] 1.74375 0.9500
#> [2,] 1.51250 0.4875
#> [3,] 1.97500 0.0250

Indicator for the presence of an arc from a (data or \(\mathcal{X}\)) point to another for CS-PCDs is the function IarcCStri. One can use it for points in the data set or for arbitrary points (as if they were in the data set). It takes the arguments, p1,p2,tri,t,M,re=NULL where p1,p2,tri,M are as in IarcPEtri and t,re=NULL are as in NCStri. This function returns \(I(p2 \in N_{CS}(p1))\), that is, returns 1 if p2 is in \(N_{CS}(p1)\), 0 otherwise.

P1<-as.numeric(runif.tri(1,Tr)$g)
P2<-as.numeric(runif.tri(1,Tr)$g)
IarcCStri(P1,P2,Tr,tau,M)
#> [1] 1
IarcCStri(Xp[1,],Xp[2,],Tr,tau,M)
#> [1] 0

Number of arcs of the CS-PCD can be computed by the function num.arcsCStri. The output is as in num.arcsPEtri.

Number of arcs of the CS-PCD can be computed by the function num.arcsCStri, which is an object of class “NumArcs” and takes arguments Xp,tri,t,M=c(1,1,1) where Xp is the data set, and the others are as above. The output is as in num.arcsPEtri.

Narcs = num.arcsCStri(Xp,Tr,t=.5,M)
summary(Narcs)
#> Call:
#> num.arcsCStri(Xp = Xp, tri = Tr, t = 0.5, M = M)
#>
#> Description of the output:
#> Number of Arcs of the CS-PCD with vertices Xp and Quantities Related to the Support Triangle
#>
#> Number of data (Xp) points in the triangle =  5
#> Number of arcs in the digraph =  0
#>
#> Indices of data points in the triangle:
#> 1 2 3 4 5 
#> 
#plot(Narcs)

The arc density of the CS-PCD can be computed by the function CSarc.dens.tri. It takes the arguments Xp,tri,t,M=c(1,1,1),in.tri.only=FALSE where Xp is the data set (or \(\mathcal{X}\) points) tri,t,M=c(1,1,1),in.tri.only=FALSE are as above and in.tri.only is as in ASarc.dens.tri.

CSarc.dens.tri(Xp,Tr,tau,M)
#> $arc.dens
#> [1] 0.35

The incidence matrix of the CS-PCD for the one triangle case can be found by inci.matCStri, using the inci.matCStri(Xp,Tr,tau,M) command. It takes the same arguments as the function num.arcsCStri.

Plot of the arcs in the digraph CS-PCD, which is based on the \(M\)-edge regions with \(M=\)(1.6,1.2). can be obtained by the function plotCSarcs.tri, which is the one-tri counterpart of the function plotCSarcs. It takes arguments Xp,tri,t,M=c(1,1,1) (as in num.arcsPEtri) and other options for the plot function. See the help page for the function using ? plotCSarcs.tri.

Plot of the arcs of the above CS-PCD, together with the edge regions (with the option edge.reg = TRUE) and vertex names added to the figure.

t<-1.5  #try also t<-2
plotCSarcs.tri(Xp,Tr,t,M,xlab="",ylab="",edge.reg = TRUE)
txt<-rbind(Tr,M)
xc<-txt[,1]+c(-.02,.02,.02,.03)
yc<-txt[,2]+c(.02,.02,.02,.03)
txt.str<-c("A","B","C","M")
text(xc,yc,txt.str)
Arcs of the CS-PCD with 10 $X$ points and edge regions (dashed lines) are based on M. The vertices and the center are labeled.

Figure 2.5: Arcs of the CS-PCD with 10 \(X\) points and edge regions (dashed lines) are based on M. The vertices and the center are labeled.

Plot of the CS proximity regions can be obtained by the function plotCSregs.tri, the first is for all points, the second is for two \(\mathcal{X}\) points only (for better visualization). It takes arguments Xp,tri,t,M=c(1,1,1) (as in num.arcsCStri) and other options for the plot function. See the help page for the function using ? plotCSregs.tri.

plotCSregs.tri(Xp,Tr,t,M,edge.reg=T,xlab="",ylab="")
CS proximity regions for the $X$ points used above.

Figure 2.6: CS proximity regions for the \(X\) points used above.

The function arcsCStri is an object of class “PCDs”. It takes arguments Xp,tri,t,M=c(1,1,1) (as in num.arcsCStri). The output list is as in the ArcsPEtri. The plot function returns the same plot as in plotCSarcs.tri, hence we comment it out below.

Arcs<-arcsCStri(Xp,Tr,t,M)
Arcs
#> Call:
#> arcsCStri(Xp = Xp, tri = Tr, t = t, M = M)
#> 
#> Type:
#> [1] "Central Similarity Proximity Catch Digraph (CS-PCD) for 2D Points in the Triangle with Expansion Parameter t = 1.5 and Center M = (1.6,1.2)"
summary(Arcs)
#> Call:
#> arcsCStri(Xp = Xp, tri = Tr, t = t, M = M)
#> 
#> Type of the digraph:
#> [1] "Central Similarity Proximity Catch Digraph (CS-PCD) for 2D Points in the Triangle with Expansion Parameter t = 1.5 and Center M = (1.6,1.2)"
#> 
#>  Vertices of the digraph =  Xp 
#>  Partition points of the region =  Tr 
#> 
#>  Selected tail (or source) points of the arcs in the digraph
#>       (first 6 or fewer are printed) 
#>          [,1]      [,2]
#> [1,] 1.687023 0.7682074
#> [2,] 1.687023 0.7682074
#> [3,] 1.687023 0.7682074
#> [4,] 1.267221 0.7722282
#> [5,] 1.482080 1.1991317
#> [6,] 1.482080 1.1991317
#> 
#>  Selected head (or end) points of the arcs in the digraph
#>       (first 6 or fewer are printed) 
#>          [,1]      [,2]
#> [1,] 1.265509 0.7442478
#> [2,] 1.267221 0.7722282
#> [3,] 1.482080 1.1991317
#> [4,] 1.265509 0.7442478
#> [5,] 1.265509 0.7442478
#> [6,] 1.687023 0.7682074
#> 
#> Parameters of the digraph
#> $center
#> [1] 1.6 1.2
#> 
#> $`expansion parameter`
#> [1] 1.5
#> 
#> Various quantities of the digraph
#>         number of vertices number of partition points 
#>                        5.0                        3.0 
#>        number of triangles             number of arcs 
#>                        1.0                        8.0 
#>                arc density 
#>                        0.4
plot(Arcs)

To see the code and the plot for the arcs using the plot.PCDs function, with vertex names and annotation added to the plot, type ? arcsCStri.

2.4 Functions for Proportional Edge PCDs with Vertices in the Standard Equilateral Triangle

We first define the standard equilateral triangle \(T_e=T(A,B,C)\) with vertices \(A=(0,0)\), \(B=(1,0)\), and \(C=(1/2,\sqrt{3}/2)\).

A<-c(0,0); B<-c(1,0); C<-c(1/2,sqrt(3)/2);
Te<-rbind(A,B,C);
n<-5  #try also n<-10, 50, or 100
set.seed(1)
Xp<-runif.std.tri(n)$gen.points
M<-c(.6,.2)  #try also M<-c(1,1,1)

Then we generate data or \(\mathcal{X}\) points of size \(n=\) 5 using the function runif.std.tri in the pcds package, and choose the arbitrary center \(M=(\) 1.6,1.2 \()\) in the interior of \(T_e\). Notice that the argument tri is redundant for the functions specific to the standard equilateral triangle, hence they are omitted for the functions which have counterparts in Section 2.2.

Plot of the triangle \(T_e\) and the \(\mathcal{X}\) points in it can be obtained by the below code, and we also add the vertex names and annotation using the text function from base R. We use asp=1 in the below plot so that the standard equilateral triangle is plotted with equal length edges.

Xlim<-range(Te[,1])
Ylim<-range(Te[,2])
plot(Te,asp=1,pch=".",xlab="",ylab="",xlim=Xlim,ylim=Ylim,main="Points in Standard Equilateral Triangle")
polygon(Te)
points(Xp)

#add the vertex names and annotation
txt<-rbind(Te)
xc<-txt[,1]+c(-.02,.02,.02)
yc<-txt[,2]+c(.01,.01,.01)
txt.str<-c("A","B","C")
text(xc,yc,txt.str)

Alternatively, we can use the plotDelaunay.tri function in pcds to obtain the same plot by executing plotDelaunay.tri(Xp,Te,xlab="x",ylab="y",main="Points in Standard Equilateral Triangle") command.

Indicator for the presence of an arc from a (data or \(\mathcal{X}\)) point to another for PE-PCDs is the function IarcPEstd.tri. One can use it for points in the data set or for arbitrary points (as if they were in the data set). It takes the arguments, p1,p2,r,M=c(1,1,1),rv=NULL as in IarcPEtri.

P1<-as.numeric(runif.tri(1,Te)$g)
P2<-as.numeric(runif.tri(1,Te)$g)
r=2
IarcPEstd.tri(P1,P2,r,M)
#> [1] 1
IarcPEstd.tri(Xp[1,],Xp[2,],r,M)
#> [1] 1

Number of arcs of the PE-PCD can be computed by the function num.arcsPEstd.triwhich which is an object of class “NumArcs” and takes arguments as the function num.arcsPEtri. The output is as in num.arcsPEtri.

Narcs = num.arcsPEstd.tri(Xp,r=1.25,M)
summary(Narcs)
#> Call:
#> num.arcsPEstd.tri(Xp = Xp, r = 1.25, M = M)
#>
#> Description of the output:
#> Number of Arcs of the PE-PCD and the Related Quantities with vertices Xp in the Standard Equilateral Triangle
#>
#> Number of data (Xp) points in the triangle =  5
#> Number of arcs in the digraph =  5
#>
#> Indices of data points in the triangle:
#> 1 2 3 4 5 
#> 
#plot(Narcs)

The incidence matrix of the PE-PCD for the one triangle case can be found by inci.matPETe, using the inci.matPETe(Xp,r,M) command.

2.5 Functions for Central Similarity PCDs with Vertices in the Standard Equilateral Triangle

We use the same setting for the data points and the center as in Section 2.4. Notice that the argument tri is redundant for the functions specific to the standard equilateral triangle, hence they are omitted for the functions which have counterparts in Section 2.3.

Indicator for the presence of an arc from a (data or \(\mathcal{X}\)) point to another for CS-PCDs is the function IarcPEstd.tri.

P1<-as.numeric(runif.tri(1,Te)$g)
P2<-as.numeric(runif.tri(1,Te)$g)
tau=1
IarcCSstd.tri(P1,P1,tau,M)
IarcCSstd.tri(P1,P2,tau,M)
IarcCSstd.tri(Xp[1,],Xp[2,],tau,M)

Number of arcs of the CS-PCD can be computed by the function num.arcsCSstd.tri which is an object of class “NumArcs” and its arguments and output are as in num.arcsCStri.

set.seed(123)
M<-as.numeric(runif.std.tri(1)$g)  #try also M<-c(.6,.2)
Narcs = num.arcsCStri(Xp,Te,t=1.5,M)
summary(Narcs)
#> Call:
#> num.arcsCStri(Xp = Xp, tri = Te, t = 1.5, M = M)
#>
#> Description of the output:
#> Number of Arcs of the CS-PCD with vertices Xp and Quantities Related to the Support Triangle
#>
#> Number of data (Xp) points in the triangle =  5
#> Number of arcs in the digraph =  3
#>
#> Indices of data points in the triangle:
#> 1 2 3 4 5 
#> 
#plot(Narcs)

The incidence matrix of the CS-PCD for the one triangle case can be found by inci.matCSstd.tri, using e.g. the inci.matCSstd.tri(Xp,t=1.5,M) command.

2.6 Auxiliary Functions to Define Proximity Regions for Points in a Triangle

The PCDs are constructed using proximity regions, and proximity region of an \(\mathcal{X}\) point depends on its location relative to the \(\mathcal{Y}\) points. In particular, AS- and PE-PCDs depend on the vertex regions and CS-PCDs depend on edge regions. We will illustrate the vertex and edge regions in this section. These regions partition the Delaunay cell (e.g., Delaunay triangle in \(\mathbb R^2\)) based on a center or central point in the triangle.

We first check whether a point is inside a triangle or not which can be done using the function in.triangle, which takes arguments p,tri,boundary=FALSE where

The function gives TRUE if the point is inside the triangle, and FALSE otherwise. It also returns the barycentric coordinates of the point with respect to the triangle.

A<-c(1,1); B<-c(2,0); C<-c(1.5,2); p<-c(1.4,1.2)
Tr<-rbind(A,B,C)
in.triangle(p,Tr)
#> $in.tri
#> [1] TRUE
#> 
#> $barycentric
#> [1] 0.4 0.2 0.4

We now illustrate circumcenter of a triangle. The function circumcenter.tri takes tri as its sole argument for a triangle and returns the circumcenter of the triangle as its output.

A<-c(1,1); B<-c(2,0); C<-c(1.5,2);
Tr<-rbind(A,B,C);  #the vertices of the triangle Tr
(CC<-circumcenter.tri(Tr)) #the circumcenter
#> [1] 2.083333 1.083333

We plot the circumcenter of an obtuse triangle below (so circumcenter is outside of the triangle) using the below code, see also the help page with ? circumcenter.tri for the code to generate this figure. Notice that in the code we used asp=1 so that lines joining CC to the edges of the triangle appear perpendicular to the edges.

D1<-(B+C)/2; D2<-(A+C)/2; D3<-(A+B)/2; #midpoints of the edges
Ds<-rbind(D1,D2,D3)

Xlim<-range(Tr[,1],CC[1])
Ylim<-range(Tr[,2],CC[2])
xd<-Xlim[2]-Xlim[1]
yd<-Ylim[2]-Ylim[1]

oldpar <- par(pty="s")
plot(A,asp=1,pch=".",xlab="",ylab="",
     main="Circumcenter of a Triangle",
     axes=TRUE,xlim=Xlim+xd*c(-.05,.05),ylim=Ylim+yd*c(-.05,.05))
polygon(Tr)
points(rbind(CC))
L<-matrix(rep(CC,3),ncol=2,byrow=TRUE); R<-Ds
segments(L[,1], L[,2], R[,1], R[,2], lty=2)

txt<-rbind(Tr,CC,Ds)
xc<-txt[,1]+c(-.08,.08,.08,.12,-.09,-.1,-.09)
yc<-txt[,2]+c(.02,-.02,.03,-.06,.02,.06,-.04)
txt.str<-c("A","B","C","CC","D1","D2","D3")
text(xc,yc,txt.str)
par(oldpar)

The function circumcenter.basic.tri is a special case of circumcenter.tri and takes the argument c1,c2 and returns the circumcenter of the standard basic triangle.

The function center.nondegPE takes arguments tri,r which are the triangle and the expansion parameter for the PE proximity regions, respectively. It returns the three centers for non-degenerate asymptotic distribution of domination number of PE-PCDs for \(r \in (1,1.5)\) and the center of mass for \(r=1.5\). This center is not defined for \(r > 1.5\), as the asymptotic distribution is degenerate in this case.

A<-c(1,1); B<-c(2,0); C<-c(1.5,2);
Tr<-rbind(A,B,C);
r<-1.35
(Ms<-center.nondegPE(Tr,r))
#>        [,1]      [,2]
#> M1 1.388889 1.0000000
#> M2 1.611111 0.7777778
#> M3 1.500000 1.2222222

We plot the non-degeneracy centers for the triangle Tr using the below code, type also ? center.nondegPE for the code to generate this figure.

Xlim<-range(Tr[,1])
Ylim<-range(Tr[,2])
xd<-Xlim[2]-Xlim[1]
yd<-Ylim[2]-Ylim[1]

plot(Tr,pch=".",xlab="",ylab="",
     main="Centers of nondegeneracy of the domination number\n of the PE-PCD in a triangle",
     axes=TRUE,xlim=Xlim+xd*c(-.05,.05),ylim=Ylim+yd*c(-.05,.05))
polygon(Tr)
points(Ms,pch=".",col=1)
polygon(Ms,lty=2)

xc<-Tr[,1]+c(-.02,.02,.02)
yc<-Tr[,2]+c(.02,.02,.03)
txt.str<-c("A","B","C")
text(xc,yc,txt.str)

xc<-Ms[,1]+c(-.04,.04,.03)
yc<-Ms[,2]+c(.02,.02,.05)
txt.str<-c(expression(M[1]),"M2","M3")
text(xc,yc,txt.str)

The function prj.cent2edges returns the projections of a point (e.g., a center) \(M\) inside a triangle to its edges, i.e., it returns the intersection point where the line joining a vertex to \(M\) crosses the opposite edge. The line segments between \(M\) the intersection points define the \(M\)-vertex regions.

A<-c(1,1); B<-c(2,0); C<-c(1.5,2);
Tr<-rbind(A,B,C);
M<-c(1.6,1.0)  #try also M<-as.numeric(runif.tri(1,Tr)$g)
(Ds<-prj.cent2edges(Tr,M))  #try also prj.cent2edges(Tr,M=c(1,1))
#>          [,1]      [,2]
#> [1,] 1.750000 1.0000000
#> [2,] 1.333333 1.6666667
#> [3,] 1.666667 0.3333333

We plot the projections of center \(M\) to the edges of the triangle Tr using the below code, type also ? prj.cent2edges for the code to generate this figure.

M<-c(1.6,1.0) 
Xlim<-range(Tr[,1])
Ylim<-range(Tr[,2])
xd<-Xlim[2]-Xlim[1]
yd<-Ylim[2]-Ylim[1]

if (dimension(M)==3) {M<-bary2cart(M,Tr)} #need to run this when M is given in barycentric coordinates

plot(Tr,pch=".",xlab="",ylab="",
     main="Projection of Center M to the edges of a triangle",axes=TRUE,
     xlim=Xlim+xd*c(-.05,.05),ylim=Ylim+yd*c(-.05,.05))
polygon(Tr)
L<-rbind(M,M,M); R<-Ds
segments(L[,1], L[,2], R[,1], R[,2], lty=2)

xc<-Tr[,1]
yc<-Tr[,2]
txt.str<-c("rv=1","rv=2","rv=3")
text(xc,yc,txt.str)

txt<-rbind(M,Ds)
xc<-txt[,1]+c(-.02,.04,-.04,-.02)
yc<-txt[,2]+c(-.02,.04,.04,-.06)
txt.str<-c("M","D1","D2","D3")
text(xc,yc,txt.str)

The function prj.cent2edges.basic.tri is a special case of prj.cent2edges taking arguments c1,c2 instead of tri and returning projections of \(M\) to the edges in the standard basic triangle.

The function prj.nondegPEcent2edges takes arguments

This function returns the projections of nondegeneracy centers (i.e. centers for non-degenerate asymptotic distribution of domination number of PE-PCDs) to its edges, i.e., it returns the intersection point where the line joining a vertex to a non-degeneracy center \(M_i\) crosses the opposite edge. The line segments between \(M_i\) the intersection points will provide the \(M_i\)-vertex regions.

A<-c(1,1); B<-c(2,0); C<-c(1.5,2);
Tr<-rbind(A,B,C);
r<-1.35
prj.nondegPEcent2edges(Tr,r,cent=2)
#>       [,1] [,2]
#> [1,] 1.825 0.70
#> [2,] 1.250 1.50
#> [3,] 1.650 0.35

We plot the projections of the non-degeneracy center \(M_1\) to the edges of a triangle using the below code, type also ? prj.nondegPEcent2edges for the code to generate this figure.

Ms<-center.nondegPE(Tr,r)
M1=Ms[1,]

Ds<-prj.nondegPEcent2edges(Tr,r,cent=1)

Xlim<-range(Tr[,1])
Ylim<-range(Tr[,2])
xd<-Xlim[2]-Xlim[1]
yd<-Ylim[2]-Ylim[1]

plot(Tr,pch=".",xlab="",ylab="",
     main="Projections from a non-degeneracy center for domination number\n of PE-PCD to the edges of the triangle",
     axes=TRUE,xlim=Xlim+xd*c(-.05,.05),ylim=Ylim+yd*c(-.05,.05))
polygon(Tr)
points(Ms,pch=".",col=1)
polygon(Ms,lty=2)

xc<-Tr[,1]+c(-.02,.03,.02)
yc<-Tr[,2]+c(-.02,.04,.04)
txt.str<-c("A","B","C")
text(xc,yc,txt.str)

txt<-Ms
xc<-txt[,1]+c(-.02,.04,-.04)
yc<-txt[,2]+c(-.02,.04,.04)
txt.str<-c("M1","M2","M3")
text(xc,yc,txt.str)

points(Ds,pch=4,col=2)
L<-rbind(M1,M1,M1); R<-Ds
segments(L[,1], L[,2], R[,1], R[,2], lty=2,lwd=2,col=4)
txt<-Ds
xc<-txt[,1]+c(-.02,.04,-.04)
yc<-txt[,2]+c(-.02,.04,.04)
txt.str<-c("D1","D2","D3")
text(xc,yc,txt.str)

The function in.triangle takes arguments

This function can be used to check whether a point p is inside a triangle tri or not.

On the other hand in.tri.all takes arguments Xp,tri,boundary where Xp is a 2D data set and tri,boundary are as in the function in.triangle. This function checks whether all of the points in a data set are inside the triangle or not.

We check in.tri.all with \(n=5\) data points generated uniformly in the unit square and in the triangle.

A<-c(1,1); B<-c(2,0); C<-c(1.5,2);
p<-c(1.4,1.2)
Tr<-rbind(A,B,C)
in.triangle(p,Tr)
#> $in.tri
#> [1] TRUE
#> 
#> $barycentric
#> [1] 0.4 0.2 0.4

#data set and checking all points in it are inside the triangle or not
n<-5
Xp1<-cbind(runif(n),runif(n))
in.tri.all(Xp1,Tr)
#> [1] FALSE

The function is.std.eq.tri takes the argument tri (a \(3 \times 2\) matrix for a triangle) and can be used for checking the triangle tri is standard equilateral triangle or not, regardless of the order of the vertices.

A<-c(0,0); B<-c(1,0); C<-c(1/2,sqrt(3)/2);
Te<-rbind(A,B,C)  #try adding +10^(-16) to each vertex
is.std.eq.tri(Te)
#> [1] TRUE

A<-c(1,1); B<-c(2,0); C<-c(1.5,2);
Tr<-rbind(A,B,C);
is.std.eq.tri(Tr)
#> [1] FALSE

The function as.basic.tri takes the arguments tri,scaled where

-tri is as in is.std.eq.tri and -scaled is a logical argument for scaling the resulting triangle. If scaled=TRUE, then the resulting triangle is scaled to be a regular basic triangle, i.e., longest edge having unit length, else the new triangle \(T(A,B,C)\) is nonscaled. The default is scaled=FALSE.

It converts any triangle to a basic triangle (up to translation and rotation), so that the output triangle is \(T(A',B',C')\) so that edges in decreasing length are \(A'B'\), \(B'C'\), and \(A'C'\). The option scaled scales the output triangle when scaled=TRUE so that longest edge \(A'B'\) has unit length (default is scaled=FALSE). Most of the times, the resulting triangle will still need to be translated and/or rotated to be in the standard basic triangle form.

c1<-.4; c2<-.6
A<-c(0,0); B<-c(1,0); C<-c(c1,c2);
as.basic.tri(rbind(B,C,A))
#> $tri
#>   [,1] [,2]
#> A  0.0  0.0
#> B  1.0  0.0
#> C  0.4  0.6
#> 
#> $desc
#> [1] "Edges (in decreasing length are) AB, BC, and AC"
#> 
#> $orig.order
#> [1] 3 1 2

x<-c(1,1); y<-c(2,0); z<-c(1.5,2);
as.basic.tri(rbind(x,y,z))
#> $tri
#>   [,1] [,2]
#> A  1.5    2
#> B  2.0    0
#> C  1.0    1
#> 
#> $desc
#> [1] "Edges (in decreasing length are) AB, BC, and AC"
#> 
#> $orig.order
#> [1] 3 2 1
as.basic.tri(rbind(x,y,z),scaled = TRUE)
#> $tri
#>        [,1]      [,2]
#> A 0.7276069 0.9701425
#> B 0.9701425 0.0000000
#> C 0.4850713 0.4850713
#> 
#> $desc
#> [1] "Edges (in decreasing length are) AB, BC, and AC"
#> 
#> $orig.order
#> [1] 3 2 1

The function tri2std.basic.tri converts a triangle to the standard basic triangle form, and its output only returns \(c_1,c_2\) in $Cvec and also the original order of the vertices in the input triangle by $orig.order.

c1<-.4; c2<-.6
A<-c(0,0); B<-c(1,0); C<-c(c1,c2);
tri2std.basic.tri(rbind(B,C,A))
#> $Cvec
#> [1] 0.4 0.6
#> 
#> $orig.order
#> [1] 3 1 2

A<-c(1,1); B<-c(2,0); C<-c(1.5,2);
tri2std.basic.tri(rbind(A,B,C))
#> $Cvec
#> [1] 0.4117647 0.3529412
#> 
#> $orig.order
#> [1] 3 2 1

Barycentric coordinates are very useful in defining and analyzing the triangular (and simplicial) proximity regions. So, we provide functions to convert barycentric coordinates to Cartesian coordinates (bary2cart) and vice versa (cart2bary). Both functions take the arguments P,tri where P is th point to change the coordinates for and tri is the reference triangle (as a \(3\times2\) matrix). As the names suggest, the function cart2bary converts the point P in Cartesian coordinates to barycentric coordinates with respect to the triangle tri, and bary2cart converts the point P in barycentric coordinates with respect to the triangle tri to Cartesian coordinates.

A<-c(1,1); B<-c(2,0); C<-c(1.5,2);
Tr<-rbind(A,B,C);
cart2bary(c(1.4,1.2),Tr)
#> [1] 0.4 0.2 0.4
bary2cart(c(1.4,1.2,1),Tr)
#> [1] 1.4722222 0.9444444

CM<-(A+B+C)/3; CM
#> [1] 1.5 1.0
cart2bary(CM,Tr)
#> [1] 0.3333333 0.3333333 0.3333333
bary2cart(c(1,1,1),Tr)
#> [1] 1.5 1.0

The function index.delaunay.tri takes the arguments

This function returns the index of the Delaunay triangle in which the given point resides.

Similarly, the function indices.delaunay.tri takes the arguments Xp,Yp,DTmesh where Xp is the set of data points for which the indices of the Delaunay triangles they reside is to be determined and Yp,DTmesh are as in index.delaunay.tri. This function returns the indices of triangles for all the points in a data set as a vector.

nx<-10 #number of X points (target)
ny<-5 #number of Y points (nontarget)

We generate \(n_x=\) 10 \(\mathcal{X}\) points uniformly in the convex hull of \(n_y=\) 5 \(\mathcal{Y}\) points using the function runif.multi.tri in pcds package.

set.seed(1)
Yp<-cbind(runif(ny),runif(ny))

Xp<-runif.multi.tri(nx,Yp)$g #data under CSR in the convex hull of Ypoints
#try also Xp<-cbind(runif(nx),runif(nx))

index.delaunay.tri(Xp[10,],Yp)
#> [1] 2

#or use
DTY<-interp::tri.mesh(Yp[,1],Yp[,2],duplicate="remove")  #Delaunay triangulation
index.delaunay.tri(Xp[10,],Yp,DTY)
#> [1] 2

(tr.ind<-indices.delaunay.tri(Xp,Yp,DTY))  #indices of the Delaunay triangles
#>  [1] 3 3 1 4 3 2 3 3 2 2

We provide the scatterplot of \(\mathcal{X}\) points (labeled according to the Delaunay triangle they reside in), and the Delaunay triangulation of \(n_y=\) 5 \(\mathcal{Y}\) points using the below code. Type also ? indices.delaunay.tri.

Xlim<-range(Yp[,1],Xp[,1])
Ylim<-range(Yp[,2],Xp[,2])
xd<-Xlim[2]-Xlim[1]
yd<-Ylim[2]-Ylim[1]

# plot of the data in the convex hull of Y points together with the Delaunay triangulation
plot(Xp,main="X Points in Delaunay Triangles for Y Points", xlab=" ", ylab=" ",
     xlim=Xlim+xd*c(-.05,.05),ylim=Ylim+yd*c(-.05,.05),pch=".")
interp::plot.triSht(DTY, add=TRUE, do.points = TRUE,pch=16,col="blue")
text(Xp,labels = factor(tr.ind) )