polyline inside closed polyline?

polyline inside closed polyline?

Anonymous
Not applicable
596 Views
8 Replies
Message 1 of 9

polyline inside closed polyline?

Anonymous
Not applicable
Im trying to write a function that determines whether a given polyline is inside of another given closed polyline. I use the standard method of drawing a ray and checking how many intersections it has with the second object. I also take into account if the polyline starts on top of the other. here is the code

Private Function fncIsInside(ByVal obj1stEnt As AcadEntity, ByVal obj2ndEnt As AcadEntity) As Boolean
Dim var1stEntPnts As Variant
Dim var2ndEntPnts As Variant
Dim varNoIntersect As Variant
Dim intNoIntersect As Integer

Dim intI As Integer
Dim intJ As Integer
Dim intK As Integer

Dim testRay As AcadRay
Dim firstPt(0 To 2) As Double
Dim secondPt(0 To 2) As Double

var1stEntPnts = obj1stEnt.Coordinates
For intI = 0 To UBound(var1stEntPnts)
intNoIntersect = 0
firstPt(0) = var1stEntPnts(intI)
firstPt(1) = var1stEntPnts(intI + 1)
firstPt(2) = 0
secondPt(0) = var1stEntPnts(intI) + 1
secondPt(1) = var1stEntPnts(intI + 1)
secondPt(2) = 0
Set testRay = ThisDrawing.ModelSpace.AddRay(firstPt, secondPt)
var2ndEntPnts = testRay.IntersectWith(obj2ndEnt, acExtendNone)
If UBound(var2ndEntPnts) > 0 Then
For intJ = 0 To UBound(var2ndEntPnts)
If var1stEntPnts(intI) <> var2ndEntPnts(intJ) And var1stEntPnts(intI + 1) <> var2ndEntPnts(intJ + 1) Then
intNoIntersect = intNoIntersect + 1
End If
intJ = intJ + 3
Next intJ
intNoIntersect = (intNoIntersect + 1) / 3
intNoIntersect = intNoIntersect Mod 2

End If
If intNoIntersect = 0 Then
fncIsInside = False
Else
fncIsInside = True
End If
intI = intI + 3

Next intI
End Function


my problem is that for some polylines it registers it as being outside when it clearly isnt, what am I doing wrong here?
0 Likes
597 Views
8 Replies
Replies (8)
Message 2 of 9

Anonymous
Not applicable
Could you use the SelectByPolygon selection set method and then check if the polyline is in the selection set.

Regards - Nathan
0 Likes
Message 3 of 9

Anonymous
Not applicable
I agree Nathan, that's what I've done to check overlaps

--
Regards
Dave Preston
<-
wrote in message news:5223722@discussion.autodesk.com...
Could you use the SelectByPolygon selection set method and then check if the
polyline is in the selection set.

Regards - Nathan
0 Likes
Message 4 of 9

Anonymous
Not applicable
this will check a 2d point is inside a 2d polyline(word wrap!)

Public Type A2DPoint
x As Integer
y As Integer
End Type

Public Type Poly2DCoordinates
CoordsList() As A2DPoint
End Type

Function ItsInside(AnyPoint As A2DPoint, AnyPoly As Poly2DCoordinates) As
Boolean
Dim i As Integer, j As Integer, npol As Integer

ItsInside = False
npol = UBound(AnyPoly.CoordsList) + 1
For i = 0 To (npol - 1)
j = (i + 1) Mod npol
If ((((AnyPoly.CoordsList(i).y <= AnyPoint.y) And (AnyPoint.y <
AnyPoly.CoordsList(j).y)) Or _
((AnyPoly.CoordsList(j).y <= AnyPoint.y) And (AnyPoint.y <
AnyPoly.CoordsList(i).y))) And _
(AnyPoint.x < (AnyPoly.CoordsList(j).x - AnyPoly.CoordsList(i).x) *
(AnyPoint.y - AnyPoly.CoordsList(i).y) _
/ (AnyPoly.CoordsList(j).y - AnyPoly.CoordsList(i).y) +
AnyPoly.CoordsList(i).x)) Then _
ItsInside = Not ItsInside
Next i
End Function

wrote in message news:5223643@discussion.autodesk.com...
Im trying to write a function that determines whether a given polyline is
inside of another given closed polyline. I use the standard method of
drawing a ray and checking how many intersections it has with the second
object. I also take into account if the polyline starts on top of the
other. here is the code

Private Function fncIsInside(ByVal obj1stEnt As AcadEntity, ByVal obj2ndEnt
As AcadEntity) As Boolean
Dim var1stEntPnts As Variant
Dim var2ndEntPnts As Variant
Dim varNoIntersect As Variant
Dim intNoIntersect As Integer

Dim intI As Integer
Dim intJ As Integer
Dim intK As Integer

Dim testRay As AcadRay
Dim firstPt(0 To 2) As Double
Dim secondPt(0 To 2) As Double

var1stEntPnts = obj1stEnt.Coordinates
For intI = 0 To UBound(var1stEntPnts)
intNoIntersect = 0
firstPt(0) = var1stEntPnts(intI)
firstPt(1) = var1stEntPnts(intI + 1)
firstPt(2) = 0
secondPt(0) = var1stEntPnts(intI) + 1
secondPt(1) = var1stEntPnts(intI + 1)
secondPt(2) = 0
Set testRay = ThisDrawing.ModelSpace.AddRay(firstPt, secondPt)
var2ndEntPnts = testRay.IntersectWith(obj2ndEnt, acExtendNone)
If UBound(var2ndEntPnts) > 0 Then
For intJ = 0 To UBound(var2ndEntPnts)
If var1stEntPnts(intI) <> var2ndEntPnts(intJ) And
var1stEntPnts(intI + 1) <> var2ndEntPnts(intJ + 1) Then
intNoIntersect = intNoIntersect + 1
End If
intJ = intJ + 3
Next intJ
intNoIntersect = (intNoIntersect + 1) / 3
intNoIntersect = intNoIntersect Mod 2

End If
If intNoIntersect = 0 Then
fncIsInside = False
Else
fncIsInside = True
End If
intI = intI + 3

Next intI
End Function


my problem is that for some polylines it registers it as being outside when
it clearly isnt, what am I doing wrong here?
0 Likes
Message 5 of 9

Anonymous
Not applicable
Problem with that is even though the vertices may be inside the polyline and edge may still cross. See attached image.

Regards - Nathan
0 Likes
Message 6 of 9

Anonymous
Not applicable
In that instance, you could also check the reverse:

check that all of poly1 vertices are inside poly2, and also check that all of poly2 vertices are NOT inside poly1.
0 Likes
Message 7 of 9

Anonymous
Not applicable
He is not speaking generally. He is looking for the borders of rooms and will only be doing 1 at a time. So if a room is inside another room, such as a bathroom in a bedroom, then each will be handled seperatly. It should not be an issue.
0 Likes
Message 8 of 9

Anonymous
Not applicable
Oh, I think this is a croos post from one on the swamp, so you would know that here. 🙂
0 Likes
Message 9 of 9

Anonymous
Not applicable
Then again, maybe I posted on the wrong thread....

I am lost.
0 Likes