From: <jpi...@us...> - 2012-05-04 09:06:57
|
Revision: 10358 http://octave.svn.sourceforge.net/octave/?rev=10358&view=rev Author: jpicarbajal Date: 2012-05-04 09:06:45 +0000 (Fri, 04 May 2012) Log Message: ----------- geometry: polygons2d Added Paths: ----------- trunk/octave-forge/main/geometry/inst/polygons2d/distancePointPolygon.m trunk/octave-forge/main/geometry/inst/polygons2d/distancePointPolyline.m trunk/octave-forge/main/geometry/inst/polygons2d/distancePolygons.m trunk/octave-forge/main/geometry/inst/polygons2d/expandPolygon.m trunk/octave-forge/main/geometry/inst/polygons2d/medialAxisConvex.m trunk/octave-forge/main/geometry/inst/polygons2d/polygonLoops.m trunk/octave-forge/main/geometry/inst/polygons2d/polygonSelfIntersections.m trunk/octave-forge/main/geometry/inst/polygons2d/polylineSelfIntersections.m trunk/octave-forge/main/geometry/inst/polygons2d/splitPolygons.m Added: trunk/octave-forge/main/geometry/inst/polygons2d/distancePointPolygon.m =================================================================== --- trunk/octave-forge/main/geometry/inst/polygons2d/distancePointPolygon.m (rev 0) +++ trunk/octave-forge/main/geometry/inst/polygons2d/distancePointPolygon.m 2012-05-04 09:06:45 UTC (rev 10358) @@ -0,0 +1,51 @@ +%% Copyright (C) 2003-2011 David Legland <dav...@gr...> +%% Copyright (C) 2012 Adapted to Octave by Juan Pablo Carbajal <car...@if...> +%% All rights reserved. +%% +%% Redistribution and use in source and binary forms, with or without +%% modification, are permitted provided that the following conditions are met: +%% +%% 1 Redistributions of source code must retain the above copyright notice, +%% this list of conditions and the following disclaimer. +%% 2 Redistributions in binary form must reproduce the above copyright +%% notice, this list of conditions and the following disclaimer in the +%% documentation and/or other materials provided with the distribution. +%% +%% THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS ''AS IS'' +%% AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE +%% IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE +%% ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE FOR +%% ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL +%% DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR +%% SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER +%% CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, +%% OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE +%% OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. +%% +%% The views and conclusions contained in the software and documentation are +%% those of the authors and should not be interpreted as representing official +%% policies, either expressed or implied, of the copyright holders. + +## -*- texinfo -*- +## @deftypefn {Function File} {@var{dist} = } distancePointPolygon (@var{point},@var{poly}) +## Compute shortest distance between a point and a polygon +## +## @seealso{polygons2d, points2d, distancePointPolyline, distancePointEdge, projPointOnPolyline} +## @end deftypefn + +function varargout = distancePointPolygon(point, poly) + + % eventually copy first point at the end to ensure closed polygon + if sum(poly(end, :)==poly(1,:))~=2 + poly = [poly; poly(1,:)]; + end + + % call to distancePointPolyline + minDist = distancePointPolyline(point, poly); + + % process output arguments + if nargout<=1 + varargout{1} = minDist; + end + +endfunction Property changes on: trunk/octave-forge/main/geometry/inst/polygons2d/distancePointPolygon.m ___________________________________________________________________ Added: svn:executable + * Added: trunk/octave-forge/main/geometry/inst/polygons2d/distancePointPolyline.m =================================================================== --- trunk/octave-forge/main/geometry/inst/polygons2d/distancePointPolyline.m (rev 0) +++ trunk/octave-forge/main/geometry/inst/polygons2d/distancePointPolyline.m 2012-05-04 09:06:45 UTC (rev 10358) @@ -0,0 +1,71 @@ +## Copyright (C) 2003-2011 David Legland <dav...@gr...> +## Copyright (C) 2012 Adapted to Octave by Juan Pablo Carbajal <car...@if...> +## All rights reserved. +## +## Redistribution and use in source and binary forms, with or without +## modification, are permitted provided that the following conditions are met: +## +## 1 Redistributions of source code must retain the above copyright notice, +## this list of conditions and the following disclaimer. +## 2 Redistributions in binary form must reproduce the above copyright +## notice, this list of conditions and the following disclaimer in the +## documentation and/or other materials provided with the distribution. +## +## THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS ''AS IS'' +## AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE +## IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE +## ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE FOR +## ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL +## DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR +## SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER +## CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, +## OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE +## OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. +## +## The views and conclusions contained in the software and documentation are +## those of the authors and should not be interpreted as representing official +## policies, either expressed or implied, of the copyright holders. + +## -*- texinfo -*- +## @deftypefn {Function File} {@var{dist} = } distancePointPolyline (@var{point},@var{poly}) +## Compute shortest distance between a point and a polyline +## Example: +## @example +## pt1 = [30 20]; +## pt2 = [30 5]; +## poly = [10 10;50 10;50 50;10 50]; +## distancePointPolyline([pt1;pt2], poly) +## ans = +## 10 +## 5 +## @end example +## +## @seealso{polygons2d, points2d,distancePointEdge, projPointOnPolyline} +## @end deftypefn + +function varargout = distancePointPolyline(point, poly, varargin) + + # number of points + Np = size(point, 1); + + # allocate memory for result + minDist = inf * ones(Np, 1); + + # process each point + for p = 1:Np + # construct the set of edges + edges = [poly(1:end-1, :) poly(2:end, :)]; + + # compute distance between current each point and all edges + dist = distancePointEdge(point(p, :), edges); + + # update distance if necessary + minDist(p) = min(dist); + end + + # process output arguments + if nargout<=1 + varargout{1} = minDist; + end + +endfunction Property changes on: trunk/octave-forge/main/geometry/inst/polygons2d/distancePointPolyline.m ___________________________________________________________________ Added: svn:executable + * Added: trunk/octave-forge/main/geometry/inst/polygons2d/distancePolygons.m =================================================================== --- trunk/octave-forge/main/geometry/inst/polygons2d/distancePolygons.m (rev 0) +++ trunk/octave-forge/main/geometry/inst/polygons2d/distancePolygons.m 2012-05-04 09:06:45 UTC (rev 10358) @@ -0,0 +1,43 @@ +## Copyright (C) 2003-2011 David Legland <dav...@gr...> +## Copyright (C) 2012 Adapted to Octave by Juan Pablo Carbajal <car...@if...> +## All rights reserved. +## +## Redistribution and use in source and binary forms, with or without +## modification, are permitted provided that the following conditions are met: +## +## 1 Redistributions of source code must retain the above copyright notice, +## this list of conditions and the following disclaimer. +## 2 Redistributions in binary form must reproduce the above copyright +## notice, this list of conditions and the following disclaimer in the +## documentation and/or other materials provided with the distribution. +## +## THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS ''AS IS'' +## AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE +## IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE +## ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE FOR +## ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL +## DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR +## SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER +## CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, +## OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE +## OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. +## +## The views and conclusions contained in the software and documentation are +## those of the authors and should not be interpreted as representing official +## policies, either expressed or implied, of the copyright holders. + +## -*- texinfo -*- +## @deftypefn {Function File} {@var{dist} = } distancePolygons (@var{poly1},@var{poly2}) +## Compute the shortest distance between 2 polygons +## +## @end deftypefn +function dist = distancePolygons(poly1, poly2) + + # compute distance of each vertex of a polygon to the other polygon + dist1 = min(distancePointPolygon(poly1, poly2)); + dist2 = min(distancePointPolygon(poly2, poly1)); + + # keep the minimum of the two distances + dist = min(dist1, dist2); + +endfunction Property changes on: trunk/octave-forge/main/geometry/inst/polygons2d/distancePolygons.m ___________________________________________________________________ Added: svn:executable + * Added: trunk/octave-forge/main/geometry/inst/polygons2d/expandPolygon.m =================================================================== --- trunk/octave-forge/main/geometry/inst/polygons2d/expandPolygon.m (rev 0) +++ trunk/octave-forge/main/geometry/inst/polygons2d/expandPolygon.m 2012-05-04 09:06:45 UTC (rev 10358) @@ -0,0 +1,85 @@ +## Copyright (C) 2003-2011 David Legland <dav...@gr...> +## Copyright (C) 2012 Adapted to Octave by Juan Pablo Carbajal <car...@if...> +## All rights reserved. +## +## Redistribution and use in source and binary forms, with or without +## modification, are permitted provided that the following conditions are met: +## +## 1 Redistributions of source code must retain the above copyright notice, +## this list of conditions and the following disclaimer. +## 2 Redistributions in binary form must reproduce the above copyright +## notice, this list of conditions and the following disclaimer in the +## documentation and/or other materials provided with the distribution. +## +## THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS ''AS IS'' +## AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE +## IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE +## ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE FOR +## ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL +## DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR +## SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER +## CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, +## OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE +## OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. +## +## The views and conclusions contained in the software and documentation are +## those of the authors and should not be interpreted as representing official +## policies, either expressed or implied, of the copyright holders. + +## -*- texinfo -*- +## @deftypefn {Function File} {@var{loops} = } expandPolygon (@var{poly}, @var{dist}) +## Expand a polygon by a given (signed) distance +## +## Associates to each edge of the polygon @var{poly} the parallel line located +## at distance @var{dist} from the current edge, and compute intersections with +## neighbor parallel lines. The resulting polygon is simplified to remove +## inner "loops", and can be disconnected. +## The result is a cell array, each cell containing a simple linear ring. +## +## This is a kind of dilation, but behaviour on corners is different. +## This function keeps angles of polygons, but there is no direct relation +## between length of 2 polygons. +## +## It is also possible to specify negative distance, and get all points +## inside the polygon. If the polygon is convex, the result equals +## morphological erosion of polygon by a ball with radius equal to the +## given distance. +## +## @seealso{polygons2d} +## @end deftypefn + +function loops = expandPolygon(poly, dist) + + # eventually copy first point at the end to ensure closed polygon + if sum(poly(end, :)==poly(1,:))~=2 + poly = [poly; poly(1,:)]; + end + + # number of vertices of the polygon + N = size(poly, 1)-1; + + # find lines parallel to polygon edges located at distance DIST + lines = zeros(N, 4); + for i=1:N + side = createLine(poly(i,:), poly(i+1,:)); + lines(i, 1:4) = parallelLine(side, dist); + end + + # compute intersection points of consecutive lines + lines = [lines;lines(1,:)]; + poly2 = zeros(N, 2); + for i=1:N + poly2(i,1:2) = intersectLines(lines(i,:), lines(i+1,:)); + end + + # split result polygon into set of loops (simple polygons) + loops = polygonLoops(poly2); + + # keep only loops whose distance to original polygon is correct + distLoop = zeros(length(loops), 1); + for i=1:length(loops) + distLoop(i) = distancePolygons(loops{i}, poly); + end + loops = loops(abs(distLoop-abs(dist))<abs(dist)/1000); + +endfunction Property changes on: trunk/octave-forge/main/geometry/inst/polygons2d/expandPolygon.m ___________________________________________________________________ Added: svn:executable + * Added: trunk/octave-forge/main/geometry/inst/polygons2d/medialAxisConvex.m =================================================================== --- trunk/octave-forge/main/geometry/inst/polygons2d/medialAxisConvex.m (rev 0) +++ trunk/octave-forge/main/geometry/inst/polygons2d/medialAxisConvex.m 2012-05-04 09:06:45 UTC (rev 10358) @@ -0,0 +1,153 @@ +## Copyright (C) 2003-2011 David Legland <dav...@gr...> +## Copyright (C) 2012 Adapted to Octave by Juan Pablo Carbajal <car...@if...> +## All rights reserved. +## +## Redistribution and use in source and binary forms, with or without +## modification, are permitted provided that the following conditions are met: +## +## 1 Redistributions of source code must retain the above copyright notice, +## this list of conditions and the following disclaimer. +## 2 Redistributions in binary form must reproduce the above copyright +## notice, this list of conditions and the following disclaimer in the +## documentation and/or other materials provided with the distribution. +## +## THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS ''AS IS'' +## AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE +## IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE +## ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE FOR +## ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL +## DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR +## SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER +## CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, +## OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE +## OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. +## +## The views and conclusions contained in the software and documentation are +## those of the authors and should not be interpreted as representing official +## policies, either expressed or implied, of the copyright holders. + +## -*- texinfo -*- +## @deftypefn {Function File} {[@var{n} @var{e}] = } medialAxisConvex (@var{polygon}) +## Compute medial axis of a convex polygon +## +## @var{polygon} is given as a set of points [x1 y1;x2 y2 ...], returns +## the medial axis of the polygon as a graph. +## @var{n} is a set of nodes. The first elements of @var{n} are the vertices of the +## original polygon. +## @var{e} is a set of edges, containing indices of source and target nodes. +## Edges are sorted according to order of creation. Index of first vertex +## is lower than index of last vertex, i.e. edges always point to newly +## created nodes. +## +## Notes: +## - Is not fully implemented, need more development (usually crashes for +## polygons with more than 6-7 points...) +## - Works only for convex polygons. +## - Complexity is not optimal: this algorithm is O(n*log n), but linear +## algorithms exist. +## +## @seealso{polygons2d, bisector} +## @end deftypefn + +function [nodes, edges] = medialAxisConvex(points) + + # eventually remove the last point if it is the same as the first one + if points(1,:) == points(end, :) + nodes = points(1:end-1, :); + else + nodes = points; + end + + # special case of triangles: + # compute directly the gravity center, and simplify computation. + if size(nodes, 1)==3 + nodes = [nodes; mean(nodes, 1)]; + edges = [1 4;2 4;3 4]; + return + end + + # number of nodes, and also of initial rays + N = size(nodes, 1); + + # create ray of each vertex + rays = zeros(N, 4); + rays(1, 1:4) = bisector(nodes([2 1 N], :)); + rays(N, 1:4) = bisector(nodes([1 N N-1], :)); + for i=2:N-1 + rays(i, 1:4) = bisector(nodes([i+1, i, i-1], :)); + end + + # add indices of edges producing rays (indices of first vertex, second + # vertex is obtained by adding one modulo N). + rayEdges = [[N (1:N-1)]' (1:N)']; + + pint = intersectLines(rays, rays([2:N 1], :)); + #ti = linePosition(pint, rays); + #ti = min(linePosition(pint, rays), linePosition(pint, rays([2:N 1], :))); + ti = distancePointLine(pint, ... + createLine(points([N (1:N-1)]', :), points((1:N)', :))); + + # create list of events. + # terms are : R1 R2 X Y t0 + # R1 and R2 are indices of involved rays + # X and Y is coordinate of intersection point + # t0 is position of point on rays + events = sortrows([ (1:N)' [2:N 1]' pint ti], 5); + + # initialize edges + edges = zeros(0, 2); + + + # ------------------- + # process each event until there is no more + + # start after index of last vertex, and process N-3 intermediate rays + for i=N+1:2*N-3 + # add new node at the rays intersection + nodes(i,:) = events(1, 3:4); + + # add new couple of edges + edges = [edges; events(1,1) i; events(1,2) i]; + + # find the two edges creating the new emanating ray + n1 = rayEdges(events(1, 1), 1); + n2 = rayEdges(events(1, 2), 2); + + # create the new ray + line1 = createLine(nodes(n1, :), nodes(mod(n1,N)+1, :)); + line2 = createLine(nodes(mod(n2,N)+1, :), nodes(n2, :)); + ray0 = bisector(line1, line2); + + # set its origin to emanating point + ray0(1:2) = nodes(i, :); + + # add the new ray to the list + rays = [rays; ray0]; + rayEdges(size(rayEdges, 1)+1, 1:2) = [n1 n2]; + + # find the two neighbour rays + ind = sum(ismember(events(:,1:2), events(1, 1:2)), 2)==0; + ir = unique(events(ind, 1:2)); + ir = ir(~ismember(ir, events(1,1:2))); + + # create new intersections + pint = intersectLines(ray0, rays(ir, :)); + #ti = min(linePosition(pint, ray0), linePosition(pint, rays(ir, :))) + events(1,5); + ti = distancePointLine(pint, line1); + + # remove all events involving old intersected rays + ind = sum(ismember(events(:,1:2), events(1, 1:2)), 2)==0; + events = events(ind, :); + + # add the newly formed events + events = [events; ir(1) i pint(1,:) ti(1); ir(2) i pint(2,:) ti(2)]; + + # and sort them according to 'position' parameter + events = sortrows(events, 5); + end + + # centroid computation for last 3 rays + nodes = [nodes; mean(events(:, 3:4))]; + edges = [edges; [unique(events(:,1:2)) ones(3, 1)*(2*N-2)]]; + +endfunction Property changes on: trunk/octave-forge/main/geometry/inst/polygons2d/medialAxisConvex.m ___________________________________________________________________ Added: svn:executable + * Added: trunk/octave-forge/main/geometry/inst/polygons2d/polygonLoops.m =================================================================== --- trunk/octave-forge/main/geometry/inst/polygons2d/polygonLoops.m (rev 0) +++ trunk/octave-forge/main/geometry/inst/polygons2d/polygonLoops.m 2012-05-04 09:06:45 UTC (rev 10358) @@ -0,0 +1,143 @@ +## Copyright (C) 2003-2011 David Legland <dav...@gr...> +## Copyright (C) 2012 Adapted to Octave by Juan Pablo Carbajal <car...@if...> +## All rights reserved. +## +## Redistribution and use in source and binary forms, with or without +## modification, are permitted provided that the following conditions are met: +## +## 1 Redistributions of source code must retain the above copyright notice, +## this list of conditions and the following disclaimer. +## 2 Redistributions in binary form must reproduce the above copyright +## notice, this list of conditions and the following disclaimer in the +## documentation and/or other materials provided with the distribution. +## +## THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS ''AS IS'' +## AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE +## IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE +## ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE FOR +## ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL +## DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR +## SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER +## CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, +## OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE +## OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. +## +## The views and conclusions contained in the software and documentation are +## those of the authors and should not be interpreted as representing official +## policies, either expressed or implied, of the copyright holders. + +## -*- texinfo -*- +## @deftypefn {Function File} {@var{loops} = } polygonLoops (@var{poly}) +## Divide a possibly self-intersecting polygon into a set of simple loops +## +## @var{poly} is a polygone defined by a series of vertices, +## @var{loops} is a cell array of polygons, containing the same vertices of the +## original polygon, but no loop self-intersect, and no couple of loops +## intersect each other. +## +## Example: +## @example +## poly = [0 0;0 10;20 10;20 20;10 20;10 0]; +## loops = polygonLoops(poly); +## figure(1); hold on; +## drawPolygon(loops); +## polygonArea(loops) +## @end example +## +## @seealso{polygons2d, polygonSelfIntersections} +## @end deftypefn + +function loops = polygonLoops(poly) + + ## Initialisations + + # compute intersections + [inters pos1 pos2] = polygonSelfIntersections(poly); + + # case of a polygon without self-intersection + if isempty(inters) + loops = {poly}; + return; + end + + # array for storing loops + loops = cell(0, 1); + + positions = sortrows([pos1 pos2;pos2 pos1]); + + + ## First loop + + pos0 = 0; + loop = polygonSubcurve(poly, pos0, positions(1, 1)); + pos = positions(1, 2); + positions(1, :) = []; + + while true + # index of next intersection point + ind = find(positions(:,1)>pos, 1, 'first'); + + # if not found, break + if isempty(ind) + break; + end + + # add portion of curve + loop = [loop;polygonSubcurve(poly, pos, positions(ind, 1))]; ##ok<AGROW> + + # look for next intersection point + pos = positions(ind, 2); + positions(ind, :) = []; + end + + # add the last portion of curve + loop = [loop;polygonSubcurve(poly, pos, pos0)]; + + # remove redundant vertices + loop(sum(loop(1:end-1,:) == loop(2:end,:) ,2)==2, :) = []; + if sum(diff(loop([1 end], :))==0)==2 + loop(end, :) = []; + end + + # add current loop to the list of loops + loops{1} = loop; + + + ## Other loops + + Nl = 1; + while ~isempty(positions) + + loop = []; + pos0 = positions(1, 2); + pos = positions(1, 2); + + while true + # index of next intersection point + ind = find(positions(:,1)>pos, 1, 'first'); + + # add portion of curve + loop = [loop;polygonSubcurve(poly, pos, positions(ind, 1))]; ##ok<AGROW> + + # look for next intersection point + pos = positions(ind, 2); + positions(ind, :) = []; + + # if not found, break + if pos==pos0 + break; + end + end + + # remove redundant vertices + loop(sum(loop(1:end-1,:) == loop(2:end,:) ,2)==2, :) = []; ##ok<AGROW> + if sum(diff(loop([1 end], :))==0)==2 + loop(end, :) = []; ##ok<AGROW> + end + + # add current loop to the list of loops + Nl = Nl + 1; + loops{Nl} = loop; + end + +endfunction Property changes on: trunk/octave-forge/main/geometry/inst/polygons2d/polygonLoops.m ___________________________________________________________________ Added: svn:executable + * Added: trunk/octave-forge/main/geometry/inst/polygons2d/polygonSelfIntersections.m =================================================================== --- trunk/octave-forge/main/geometry/inst/polygons2d/polygonSelfIntersections.m (rev 0) +++ trunk/octave-forge/main/geometry/inst/polygons2d/polygonSelfIntersections.m 2012-05-04 09:06:45 UTC (rev 10358) @@ -0,0 +1,87 @@ +## Copyright (C) 2003-2011 David Legland <dav...@gr...> +## Copyright (C) 2012 Adapted to Octave by Juan Pablo Carbajal <car...@if...> +## All rights reserved. +## +## Redistribution and use in source and binary forms, with or without +## modification, are permitted provided that the following conditions are met: +## +## 1 Redistributions of source code must retain the above copyright notice, +## this list of conditions and the following disclaimer. +## 2 Redistributions in binary form must reproduce the above copyright +## notice, this list of conditions and the following disclaimer in the +## documentation and/or other materials provided with the distribution. +## +## THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS ''AS IS'' +## AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE +## IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE +## ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE FOR +## ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL +## DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR +## SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER +## CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, +## OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE +## OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. +## +## The views and conclusions contained in the software and documentation are +## those of the authors and should not be interpreted as representing official +## policies, either expressed or implied, of the copyright holders. + +## -*- texinfo -*- +## @deftypefn {Function File} {@var{pts} = } polygonSelfIntersections (@var{poly}) +## @deftypefnx {Function File} {[@var{pts} @var{pos1} @var{pos2}] = } polygonSelfIntersections (@var{poly}) +## Find-self intersection points of a polygon +## +## Return the position of self intersection points +## +## Also return the 2 positions of each intersection point (the position +## when meeting point for first time, then position when meeting point +## for the second time). +## +## Example +## @example +## # use a '8'-shaped polygon +## poly = [10 0;0 0;0 10;20 10;20 20;10 20]; +## polygonSelfIntersections(poly) +## ans = +## 10 10 +## @end example +## +## @seealso{polygons2d, polylineSelfIntersections} +## @end deftypefn + +function varargout = polygonSelfIntersections(poly, varargin) + + tol = 1e-14; + + # ensure the last point equals the first one + if sum(abs(poly(end, :)-poly(1,:)) < tol) ~= 2 + poly = [poly; poly(1,:)]; + end + + # compute intersections by calling algo for polylines + [points pos1 pos2] = polylineSelfIntersections(poly); + + # It may append that first vertex of polygon is detected as intersection, + # the following tries to detect this + n = size(poly, 1) - 1; + inds = (pos1 == 0 & pos2 == n) | (pos1 == n & pos2 == 0); + points(inds, :) = []; + pos1(inds) = []; + pos2(inds) = []; + + # remove multiple intersections + [points I J] = unique(points, 'rows', 'first'); ##ok<NASGU> + pos1 = pos1(I); + pos2 = pos2(I); + + + ## Post-processing + + # process output arguments + if nargout <= 1 + varargout = {points}; + elseif nargout == 3 + varargout = {points, pos1, pos2}; + end + +endfunction Property changes on: trunk/octave-forge/main/geometry/inst/polygons2d/polygonSelfIntersections.m ___________________________________________________________________ Added: svn:executable + * Added: trunk/octave-forge/main/geometry/inst/polygons2d/polylineSelfIntersections.m =================================================================== --- trunk/octave-forge/main/geometry/inst/polygons2d/polylineSelfIntersections.m (rev 0) +++ trunk/octave-forge/main/geometry/inst/polygons2d/polylineSelfIntersections.m 2012-05-04 09:06:45 UTC (rev 10358) @@ -0,0 +1,153 @@ +## Copyright (C) 2003-2011 David Legland <dav...@gr...> +## Copyright (C) 2012 Adapted to Octave by Juan Pablo Carbajal <car...@if...> +## All rights reserved. +## +## Redistribution and use in source and binary forms, with or without +## modification, are permitted provided that the following conditions are met: +## +## 1 Redistributions of source code must retain the above copyright notice, +## this list of conditions and the following disclaimer. +## 2 Redistributions in binary form must reproduce the above copyright +## notice, this list of conditions and the following disclaimer in the +## documentation and/or other materials provided with the distribution. +## +## THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS ''AS IS'' +## AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE +## IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE +## ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE FOR +## ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL +## DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR +## SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER +## CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, +## OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE +## OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. +## +## The views and conclusions contained in the software and documentation are +## those of the authors and should not be interpreted as representing official +## policies, either expressed or implied, of the copyright holders. + +## -*- texinfo -*- +## @deftypefn {Function File} {@var{pts} = } polylineSelfIntersections (@var{poly}) +## Find self-intersections points of a polyline +## +## Return the position of self intersection points +## +## Also return the 2 positions of each intersection point (the position +## when meeting point for first time, then position when meeting point +## for the second time). +## +## Example +## @example +## # use a gamma-shaped polyline +## poly = [0 0;0 10;20 10;20 20;10 20;10 0]; +## polylineSelfIntersections(poly) +## ans = +## 10 10 +## +## # use a 'S'-shaped polyline +## poly = [10 0;0 0;0 10;20 10;20 20;10 20]; +## polylineSelfIntersections(poly) +## ans = +## 10 10 +## @end example +## +## @seealso{polygons2d, intersectPolylines, polygonSelfIntersections} +## @end deftypefn + +function varargout = polylineSelfIntersections(poly, varargin) + + ## Initialisations + + # determine whether the polyline is closed + closed = false; + if ~isempty(varargin) + closed = varargin{1}; + if ischar(closed) + if strcmp(closed, 'closed') + closed = true; + elseif strcmp(closed, 'open') + closed = false; + end + end + end + + # if polyline is closed, ensure the last point equals the first one + if closed + if sum(abs(poly(end, :)-poly(1,:))<1e-14)~=2 + poly = [poly; poly(1,:)]; + end + end + + # arrays for storing results + points = zeros(0, 2); + pos1 = zeros(0, 1); + pos2 = zeros(0, 1); + + # number of vertices + Nv = size(poly, 1); + + + ## Main processing + + # index of current intersection + ip = 0; + + # iterate over each couple of edge ( (N-1)*(N-2)/2 iterations) + for i=1:Nv-2 + # create first edge + edge1 = [poly(i, :) poly(i+1, :)]; + for j=i+2:Nv-1 + # create second edge + edge2 = [poly(j, :) poly(j+1, :)]; + + # check conditions on bounding boxes + if min(edge1([1 3]))>max(edge2([1 3])) + continue; + end + if max(edge1([1 3]))<min(edge2([1 3])) + continue; + end + if min(edge1([2 4]))>max(edge2([2 4])) + continue; + end + if max(edge1([2 4]))<min(edge2([2 4])) + continue; + end + + # compute intersection point + inter = intersectEdges(edge1, edge2); + + if sum(isfinite(inter))==2 + # add point to the list + ip = ip + 1; + points(ip, :) = inter; + + # also compute positions on the polyline + pos1(ip, 1) = i+edgePosition(inter, edge1)-1; + pos2(ip, 1) = j+edgePosition(inter, edge2)-1; + end + end + end + + # if polyline is closed, the first vertex was found as an intersection, so + # we need to remove it + if closed + dist = distancePoints(points, poly(1,:)); + [minDist ind] = min(dist); ##ok<ASGLU> + points(ind,:) = []; + pos1(ind) = []; + pos2(ind) = []; + end + + ## Post-processing + + # process output arguments + if nargout<=1 + varargout{1} = points; + elseif nargout==3 + varargout{1} = points; + varargout{2} = pos1; + varargout{3} = pos2; + end + +endfunction Property changes on: trunk/octave-forge/main/geometry/inst/polygons2d/polylineSelfIntersections.m ___________________________________________________________________ Added: svn:executable + * Added: trunk/octave-forge/main/geometry/inst/polygons2d/splitPolygons.m =================================================================== --- trunk/octave-forge/main/geometry/inst/polygons2d/splitPolygons.m (rev 0) +++ trunk/octave-forge/main/geometry/inst/polygons2d/splitPolygons.m 2012-05-04 09:06:45 UTC (rev 10358) @@ -0,0 +1,64 @@ +## Copyright (C) 2003-2011 David Legland <dav...@gr...> +## Copyright (C) 2012 Adapted to Octave by Juan Pablo Carbajal <car...@if...> +## All rights reserved. +## +## Redistribution and use in source and binary forms, with or without +## modification, are permitted provided that the following conditions are met: +## +## 1 Redistributions of source code must retain the above copyright notice, +## this list of conditions and the following disclaimer. +## 2 Redistributions in binary form must reproduce the above copyright +## notice, this list of conditions and the following disclaimer in the +## documentation and/or other materials provided with the distribution. +## +## THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS ''AS IS'' +## AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE +## IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE +## ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE FOR +## ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL +## DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR +## SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER +## CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, +## OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE +## OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. +## +## The views and conclusions contained in the software and documentation are +## those of the authors and should not be interpreted as representing official +## policies, either expressed or implied, of the copyright holders. + +## -*- texinfo -*- +## @deftypefn {Function File} {@var{polygons} = } splitPolygons (@var{polygon}) +## Convert a NaN separated polygon list to a cell array of polygons. +## +## @var{polygon} is a N-by-2 array of points, with possibly couples of NaN values. +## The functions separates each component separated by NaN values, and +## returns a cell array of polygons. +## +## @seealso{polygons2d} +## @end deftypefn +function polygons = splitPolygons(polygon) + + if iscell(polygon) + # case of a cell array + polygons = polygon; + + elseif sum(isnan(polygon(:)))==0 + # single polygon -> no break + polygons = {polygon}; + + else + # find indices of NaN couples + inds = find(sum(isnan(polygon), 2)>0); + + # number of polygons + N = length(inds)+1; + polygons = cell(N, 1); + + # iterate over NaN-separated regions to create new polygon + inds = [0;inds;size(polygon, 1)+1]; + for i=1:N + polygons{i} = polygon((inds(i)+1):(inds(i+1)-1), :); + end + end + +endfunction This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |