SPATIAL-YAP. David Vaz, Michel Ferreira, Ricardo Lopes. DCC-FC & LIACC University of Porto, Portugal

Size: px
Start display at page:

Download "SPATIAL-YAP. David Vaz, Michel Ferreira, Ricardo Lopes. DCC-FC & LIACC University of Porto, Portugal"

Transcription

1 SPATIAL-YAP David Vaz, Michel Ferreira, Ricardo Lopes DCC-FC & LIACC University of Porto, Portugal 1 Introduction Spatial Yap results from a interface between three components. The MYDDAS interface, with support to OGC Geometry types, a spatial operators library OGC and a visualization component SIMPLEGRAPHICS. We will next describe the spatial terms and the spatial predicates component, and then the SIMPLE- GRAPHICS component. MYDDAS is already well documented and therefor we will not explain its use. 2 Spatial Terms and Operators The spatial objects, or geometry objects, in prolog follows the OpenGIS standard [?]. The geometry types follow an object oriented scheme described in Figure 1. The attributes, methods, restrictions and prolog representation will be explained next. To use the following predicates we need to load the OGC library, using use module(library(ogc)) prolog call. Geometry Point Curve Surface Geometry Collection Linestring Polygon MultiCurve MultiPoint MultiSurface MultiLinestring MultiPolygon Fig.1. Geometry-types (abstract types in gray). 2.1 Geometry Geometry is root class of the hierarchy, although it is an abstract type all the geometric objects inherits the methods from geometry.

2 Basic on Geometry ogc envelope(+geometry,-polygon) Returns the rectangle bounding the Geometry as a Polygon. The polygon is defined by the corner points of the bounding box ((MINX,MINY), (MAXX,MINY), (MAXX,MAXY), (MINX,MAXY), (MINX,MINY)). ogc is empty(+geometry) Succeeds if the Geometry corresponds to the empty set. ogc is simple(+geometry) Succeeds if the Geometry is simple. ogc boundary(+geometry,-boundary) Returns the Geometry Boundary. for testing Spatial Relations between geometric objects ogc equals(+geometry1,+geometry2) Succeeds if Geometry1 and Geometry2 are spatially equal. ogc disjoint(+geometry1,+geometry2) Succeeds if Geometry1 and Geometry2 are spatially disjoint, i.e., if the given geometry s do no intersect. ogc touches(+geometry1,+geometry2) Succeeds if Geometry1 spatially touches Geometry2. Two geometries spatially touch if the interior of both geometries do not intersect, but the boundary of one of the geometries intersects either the boundary or the interior of the other. ogc within(+geometry1,+geometry2) Succeeds if Geometry1 is completely within Geometry2. ogc overlaps(+geometry1,+geometry2) Succeeds if Geometry1 spatially overlaps Geometry2. The term spatially overlaps is used if two geometries intersect and their intersection results in a geometry of the same dimension but not equal to either of the given geometries. ogc crosses(+geometry1,+geometry2) Succeeds if Geometry1 spatially crosses Geometry2. The term spatially crosses denotes a spatial relation when two given geometries intersect, and their intersection results in a geometry that has a dimension that is one less than the maximum dimension of the two given geometries, and the intersection is not equal to any of the two given geometries. ogc intersects(+geometry1,+geometry2) Succeeds if Geometry1 spatially intersects Geometry2. ogc contains(+geometry1,+geometry2) Succeeds if Geometry1 is completely contained in Geometry2. that support Spatial Analysis ogc distance(+geometry1,+geometry2,-distance) Returns the shortest Distance between any two points in the two geometries.

3 ogc buffer(+geometry,+distance,-buffer) Returns a geometry (Buffer) that represents all points whose distance from this Geometry is less than or equal to Distance. ogc convex hull(+geometry,-convexhull) Returns a geometry (ConvexHull) that is the convex hull of this Geometry. ogc intersection(+geometry1,+geometry2,-geometry) Returns the Geometry that represents the point set intersection of Geometry1 with Geometry2. ogc union(+geometry1,+geometry2,-geometry) Returns the Geometry that represents the point set union of Geometry1 and Geometry2. ogc difference(+geometry1,+geometry2,-geometry) Returns the Geometry that represents the point set difference of Geometry1 and Geometry2. ogc symmetric difference(+geometry1,+geometry2,-geometry) Returns the Geometry that represents the point set symmetric difference of Geometry1 and Geometry Point A Point is a zero-dimensional spatial object, that represents a single location and have two coordinates (x,y). The boundary of a point is empty. In prolog point(x,y). 2.3 Linestring A Linestring is a one-dimensional spatial object and is defined as a list of points with linear interpolation. The list must have at least two points. A Linestring is simple if if does not pass through the same point twice. A Linestring is closed if the start point is equal to the end point. A simple and closed Linestring is a linear ring. The boundary of a Linestring are the end points, except with a closed Linestring where the boundary is empty. In prolog linestring([(x1,y1),(x2,y2) ]), Figure 2 shows some examples of linestrings. ogc length(+linestring,-length) Returns the Length of the Linestring. ogc is closed(+linestring) Succeeds if the Linestring is closed. ogc is ring(+linestring) Succeeds if the Linestring is a ring.

4 linestring([(1,1),(-1,0),(0,-1),(0,0)]) is simple. linestring([(1,1),(-1,0),(0,-1),(0,1)]) is non-simple. linestring([(1,1),(-1,0),(0,-1),(1,1)]) is simple and closed (linear ring). Fig.2. Examples of linestrings. 2.4 Polygon A Polygon is a two-dimensional spatial object that defines a planar surface. It is defined by one exterior boundary and zero or more interior boundaries. Each interior boundary defines a hole in the Polygon. The Polygon boundaries are defined by linear rings. The boundary of a Polygon consists of the set of linear rings that defines it. There are some more assertions on how to define a valid polygon that can be found in OpenGis standard??. The Prolog representation uses a list of linear rings with at least one linear ring the exterior boundary, which is always the first in the list. Eg. polygon( [Exterior Holes]) see Figure 3 for examples. polygon([[(3,0),(5,3),(6,7),(0,9), (3,7),(3,3),(0,4),(3,0)]]) polygon([[(3,0),(6,3),(6,7),(3,10), (0,7),(0,3),(3,0)], [(3,3),(2,4),(2,6), (3,8),(4,5),(3,3)]]) Fig.3. Examples of polygons ogc area(+polygon,-area) Returns the Area of the Polygon. ogc centroid(+polygon,-point) Returns the mathematical centroid for this Polygon as a Point. The result is not guaranteed to be on this Polygon.

5 ogc point on surface(+polygon,-point) Returns a Point guaranteed to be on this Polygon. 2.5 Multipoint A Multipoint is a zero-dimensional spatial object, consisting of a list of points with at least one point. A Multipoint is simple if there are no duplicates in the list of points. The boundary of a Multipoint is empty. In Prolog multipoint([point ]), E.g. multipoint([(3,0),(5,3),(6,7), (0,9),(3,7),(3,3),(0,4),(3,0)]). 2.6 Multilinestring A Multilinestring is a one-dimensional spatial object, consisting of a list of linestrings. A Multilinestring is simple if and only if all of its elements are simple and the only intersections between any two elements occur in the elements boundaries. The boundary of a Multilinestring is the set of Points that are boundaries of an odd number of elements. A Multilinestring is closed if all of its elements are closed. In Prolog multilinestring([linestring ]). ogc length(+multilinestring,-length) Returns the Length of the Multilinestring, which is equal to the sum of the lengths of the Multilinestring elements. ogc is closed(+multilinestring) Succeeds if the Multilinestring is closed. 2.7 Multipolygon Multipolygon is a two-dimensional spatial object, consisting of a list of polygons. The Boundary of a Multipolygon is the set of boundaries of its elements. As with Polygon there are some more assertions on how to define a valid Multipolygon that can be found in OpenGis standard??. In Prolog multipolygon([polygon ]). ogc area(+multipolygon,-area) Returns the Area of the Multipolygon, which is equal to the sum of the areas of the Multipolygon elements. ogc centroid(+multipolygon,-point) Returns the mathematical centroid for this Multipolygon as a Point. The result is not guaranteed to be on this Multipolygon. ogc point on surface(+multipolygon,-point) Returns a Point guaranteed to be on this Multipolygon.

6 2.8 Geometrycollection Geometrycollection is a spatial object consisting of a list of zero or more spatial objects. A Geometrycollection with zero elements represents the empty set. In Prolog geometrycollection([ ]). geometrycollection([ linestring([(0,0),(0,7),(9,7),(9,0),(0,0)]), multilinestring([[(0,3),(1,3)],[(7,3),(9,3)], [(4,6),(4,7)]]), multipolygon([ [[(0,0),(3,0),(1,2),(0,2),(0,0)]], [[(5,0),(7,2),(9,2),(9,0),(5,0)]], [[(0,4),(1,4),(3,6),(3,7),(0,7),(0,4)]], [[(5,7),(9,7),(9,4),(7,4),(5,6),(5,7)]], [[(7,3),(6.4,2.8),(6.4,3.2),(7,3)]], [[(1,3),(1.6,2.8),(1.6,3.2),(1,3)]]]), polygon([[(3,3),(4,4),(5,3),(4,2),(3,3)], [(3.6,3.4),(3.6,2.6),(4.4,2.6), (4.4,3.4),(3.6,3.4)]]) ]) Fig.4. Example of a geometrycollection 3 Visualization of spatial data with simplegraphics This section describes how to visualize spatial data, first we need to load the library using use module(library(simplegraphics)). The module has three major modes, OpenGl, Allegro and Postscript. For now only PostScript is recommended, given that OpenGL and Allegro are not stable. 3.1 Module Initialization and Shutdown sg initialize(+options) This is a backtracable predicate, in the first call it initializes the Spatial module and creates the window where the objects will be displayed. The second call will terminate the use of the window and the module, failing. Options is a list with possibly none of the following options: system(+system) System defines the window type, either opengl, allegro or nowindow (defaults to nowindow); size(+x,+y) defining the window, or the postscript size (defaults to 800x600). color(+r,+g,+b) defining the default color (defaults to white). background(+r,+g,+b) defining the background color (defaults to black) sg shutdown Shutdown the spatial module, and window interface. sg recenter Recenters the spatial module, based in the spatial objects created. sg export(+type,+file) For now only ps is supported as export type. This predicate exports the spatial objects to a postscript file File.

7 3.2 Drawing spatial Terms Spatial objects are stored in a list, used to display them in the window. They are drawn using the same order as they where created, so the later object will be drawn in front of a previous one. sg create(+geometry) sg create is the main predicate to create spatial objects. Geometry must be a valid spatial object, as described in the previous section. This is a backtracable predicate, but with only two alternatives, the first one inserts the object in the list, the second removes the object from the list, failing. sg color(+red,+green,+blue) Changes the color. The color components are in RGB format varying from 0 to 255. As with the sg create and transformations this is a backtracable predicate, and is also inserted in the list, so only objects inserted afterward are affected by sg color. There are also some alias to the following colors: black, white, red, green, blue, yellow, magenta and cyan. Color alias can be used with sg color/ Transformations We also allow the use of transformations, to simplify the programming process. The transformations are also stored in the list, in the same order as they are inserted, so the transformations will affect all objects created afterward, including other transformations, this will be better explained bellow. All the predicates are similar to sg create, as they are backtracable and have the same alternatives. sg translate(+x,+y) Translates by (X,Y). Arguments must be numbers. sg rotate(+angle) Rotates the objects by Angle in a counter-clockwise direction. Angle is in degrees. sg scale(+x,+y) Scales by (X,Y). sg identity Resets previous transformations, so the next objects or transformations are not affected by them. Transformations order can be tricky, especially in the first approach. Imagine a square centered in the origin, what will be the result of applying a rotation of

8 1 - Rotate, 2 - Translate. draw :- draw_square, sg_translate(4,0), sg_rotate(45), draw_square. 1 - Translate, 2 - Rotate. draw :- draw_square, sg_rotate(45), sg_translate(4,0), draw_square. Fig.5. Rotating and Translating orders 45 degrees and a translation, and if we apply the translation first? In Figure 5 we have the result. Now lets think about how to specify the transformations. This API was greatly influenced by OpenGL and its matrix scheme. In fact in the software approach we emulate the matrix transformations. Transformations are specified in the reverse order, so the closer transformation is applied first, in Figure 5 the second square to be drawn exemplifies precisely this. 3.4 Interaction between YAP and SPATIAL-YAP Being the window one of the main components of SPATIAL-YAP, we have created a simple way of manipulation of the display aspect. We allow zooming and padding, so it is possible to change the view of the objects. This also releases the programmer from the task of defining the best display of the objects. To have this manipulation we need to have the window working in the same time as YAP, otherwise we would need to pause YAP for displaying purposes, which is not a good idea. Having both systems working in the same time, prolog can be being evaluated in the same time as the user manipulates the window, allowing to have an interactive view of the objects. sg pause, sg pause(+n) Pauses the display for 1/N frame/s. sg yield Gives control to the window, pausing the execution of YAP. When the user presses y in the window, YAP continues, from the point where it was yield.

9 sg repeat Similar to the standard Prolog repeat. The difference is that it only succeeds while the window exists. 3.5 Examples Hanoi Puzzle We will now show how to animate a simple algorithm with spatial-yap, a typical prolog program to solve Hanoi puzzle is given in Figure 6. hanoi :- move(3, left, right, center). move(0, _, _, _) :-!. move(n, X, Y, Z) :- M is N-1, move(m, X, Z, Y), inform(x, Y), move(m, Z, Y, X). inform(x, Y) :- write( move a disc from the ), write(x), write( pole to the ), write(y), write( pole ), nl. Fig.6. Hanoi Puzzle in Prolog To have this animated, we need to draw poles and disks. Poles can be simple linestrings and disks can be rectangles, this is done with draw pole/0 and draw disk/1 in Figure 7. You might notice that we are creating poles and disks in a generic form, the true position will be given by the transformations. For example, draw base/0 draws the three poles using translations and resets all the transformations with sg identity/1 at the end. The algorithm in Figure 6 does not need to have the global state of the poles. However, to graphically display the disks positions and the transitions from pole to pole we need to have the state of each pole. Also instead of informing the disks changes we will actually change disks from pole to pole. So move/3 will be changed to move/5 receiving a pole list and returning the updated one. At the beginning the state is [1-[1,2,3],2-[],3-[]]. The new move/5 can be seen in Figure 8. Now we only need to draw the solving process. As we want to have an animated version we need to clear the disks positions after any change. We display the disks positions, pause for some time and then fail, to clear the display. We use draw step/1 for this purpose, and display the disks state after each manipulation. In the end we display the disks state and yield the control to the graphics subsystem. The complete code is in Figure 9.

10 draw_pole :- sg_create(linestring([(0,0),(0,4)])), sg_create(linestring([(-4,0),(4,0)])). draw_disk(n) :- NN is -N, sg_create(polygon([[(nn,0),(n,0),(n,1),(nn,1),(nn,0)]])). draw_base :- draw_pole, sg_translate(8,0), draw_pole, sg_translate(8,0), draw_pole, sg_identity. Fig. 7. Base drawing for Hanoi. move(0, _, _, _, L, L) :-!. move(n, X, Y, Z, LIn, LOut) :- M is N-1, move(m, X, Z, Y, LIn, L1), move_disk(x, Y, L1, L2), move(m, Z, Y, X, L2, LOut). Fig. 8. New move/5.

11 draw_pole :- sg_create(linestring([(0,0),(0,4)])), sg_create(linestring([(-4,0),(4,0)])). draw_base :- sg_color(red), draw_pole, sg_translate(8,0), draw_pole, sg_translate(8,0), draw_pole, sg_identity, sg_color(white). draw_disk(n) :- NN is -N, sg_create(polygon([[(nn,0),(n,0),(n,1),(nn,1),(nn,0)]])). draw_disks([]). draw_disks([h T]) :- draw_disks(t), draw_disk(h), sg_translate(0,1). draw_disks_list([]). draw_disks_list([_-l T]) :- draw_disks(l), length(l,ll), NLL is -LL, sg_translate(8,nll), draw_disks_list(t). draw_step(l) :- draw_disks_list(l), sg_pause(10), fail. draw_step(_). move_(x,y,[x-[y T] Ts],[X-T Ts]) :-!. move_(x,y,[h T],[H NT]) :- move_(x,y,t,nt). move_disk(x,y,l,nl) :- move_(x,d,l,nl1), move_(y,d,nl,nl1). move(0, _, _, _, L, L) :-!. move(n, X, Y, Z, LIn, LOut) :- M is N-1, move(m, X, Z, Y, LIn, L1), draw_step(l1), move_disk(x, Y, L1, L2), draw_step(l2), move(m, Z, Y, X, L2, LOut), draw_step(lout). hanoi :- sg_initialize([system(allegro)]), draw_base, sg_recenter, L = [1-[1,2,3],2-[],3-[]], move(3,1,2,3,l,sol), draw_disks_list(sol), sg_yield, sg_shutdown. Fig.9. Hanoi Puzzle with spatial yap

Secrets of the JTS Topology Suite

Secrets of the JTS Topology Suite Secrets of the JTS Topology Suite Martin Davis Refractions Research Inc. Overview of presentation Survey of JTS functions and components Tips for using JTS as an engine for processing Geometry Tips for

More information

Analytical and Computer Cartography Winter Lecture 9: Geometric Map Transformations

Analytical and Computer Cartography Winter Lecture 9: Geometric Map Transformations Analytical and Computer Cartography Winter 2017 Lecture 9: Geometric Map Transformations Cartographic Transformations Attribute Data (e.g. classification) Locational properties (e.g. projection) Graphics

More information

SVENSK STANDARD SS-ISO :2004. Geografisk information Hantering av enklare objekt Del 1: Arkitektur (ISO :2004, IDT)

SVENSK STANDARD SS-ISO :2004. Geografisk information Hantering av enklare objekt Del 1: Arkitektur (ISO :2004, IDT) SVENSK STANDARD Fastställd 2004-09-24 Utgåva 1 Geografisk information Hantering av enklare objekt Del 1: Arkitektur (ISO 19125-1:2004, IDT) Geographic information Simple feature access Part 1: Common architecture

More information

Introduction. Computer Vision & Digital Image Processing. Preview. Basic Concepts from Set Theory

Introduction. Computer Vision & Digital Image Processing. Preview. Basic Concepts from Set Theory Introduction Computer Vision & Digital Image Processing Morphological Image Processing I Morphology a branch of biology concerned with the form and structure of plants and animals Mathematical morphology

More information

pine cone Ratio = 13:8 or 8:5

pine cone Ratio = 13:8 or 8:5 Chapter 10: Introducing Geometry 10.1 Basic Ideas of Geometry Geometry is everywhere o Road signs o Carpentry o Architecture o Interior design o Advertising o Art o Science Understanding and appreciating

More information

PostGIS: future developments

PostGIS: future developments PostGIS: future developments What is PostGIS GPL PostgreSQL extension for Geographic Objects Types Operators Functions Indexes Standard interfaces Extension API Current features OpenGIS Simple Features

More information

09/11/2017. Morphological image processing. Morphological image processing. Morphological image processing. Morphological image processing (binary)

09/11/2017. Morphological image processing. Morphological image processing. Morphological image processing. Morphological image processing (binary) Towards image analysis Goal: Describe the contents of an image, distinguishing meaningful information from irrelevant one. Perform suitable transformations of images so as to make explicit particular shape

More information

CS 559 Computer Graphics Midterm Exam March 22, :30-3:45 pm

CS 559 Computer Graphics Midterm Exam March 22, :30-3:45 pm CS 559 Computer Graphics Midterm Exam March 22, 2010 2:30-3:45 pm This exam is closed book and closed notes. Please write your name and CS login on every page! (we may unstaple the exams for grading) Please

More information

Dgp _ lecture 2. Curves

Dgp _ lecture 2. Curves Dgp _ lecture 2 Curves Questions? This lecture will be asking questions about curves, their Relationship to surfaces, and how they are used and controlled. Topics of discussion will be: Free form Curves

More information

Measurement and Geometry (M&G3)

Measurement and Geometry (M&G3) MPM1DE Measurement and Geometry (M&G3) Please do not write in this package. Record your answers to the questions on lined paper. Make notes on new definitions such as midpoint, median, midsegment and any

More information

Introduction to the Dimensionally Extended 9 Intersection Model (DE-9IM) in PostgreSQL/PostGIS Tutorial

Introduction to the Dimensionally Extended 9 Intersection Model (DE-9IM) in PostgreSQL/PostGIS Tutorial Introduction to the Dimensionally Extended 9 Intersection Model (DE-9IM) in PostgreSQL/PostGIS Tutorial Germán Carrillo gcarrillo@uni-muenster.de geotux_tuxman@linuxmail.org Objectives Following this tutorial

More information

ISO INTERNATIONAL STANDARD. Geographic information Simple feature access Part 1: Common architecture

ISO INTERNATIONAL STANDARD. Geographic information Simple feature access Part 1: Common architecture INTERNATIONAL STANDARD ISO 19125-1 First edition 2004-08-01 Corrected version 2004-11-01 Geographic information Simple feature access Part 1: Common architecture Information géographique Accès aux entités

More information

layers in a raster model

layers in a raster model layers in a raster model Layer 1 Layer 2 layers in an vector-based model (1) Layer 2 Layer 1 layers in an vector-based model (2) raster versus vector data model Raster model Vector model Simple data structure

More information

Planar Graphs. 1 Graphs and maps. 1.1 Planarity and duality

Planar Graphs. 1 Graphs and maps. 1.1 Planarity and duality Planar Graphs In the first half of this book, we consider mostly planar graphs and their geometric representations, mostly in the plane. We start with a survey of basic results on planar graphs. This chapter

More information

Computational Geometry

Computational Geometry Lecture 1: Introduction and convex hulls Geometry: points, lines,... Geometric objects Geometric relations Combinatorial complexity Computational geometry Plane (two-dimensional), R 2 Space (three-dimensional),

More information

Graphics and Java 2D Introduction OBJECTIVES. One picture is worth ten thousand words.

Graphics and Java 2D Introduction OBJECTIVES. One picture is worth ten thousand words. 1 2 12 Graphics and Java 2D One picture is worth ten thousand words. Chinese proverb Treat nature in terms of the cylinder, the sphere, the cone, all in perspective. Paul Cézanne Colors, like features,

More information

Announcements. Data Sources a list of data files and their sources, an example of what I am looking for:

Announcements. Data Sources a list of data files and their sources, an example of what I am looking for: Data Announcements Data Sources a list of data files and their sources, an example of what I am looking for: Source Map of Bangor MEGIS NG911 road file for Bangor MEGIS Tax maps for Bangor City Hall, may

More information

CSCI 4620/8626. Computer Graphics Clipping Algorithms (Chapter 8-5 )

CSCI 4620/8626. Computer Graphics Clipping Algorithms (Chapter 8-5 ) CSCI 4620/8626 Computer Graphics Clipping Algorithms (Chapter 8-5 ) Last update: 2016-03-15 Clipping Algorithms A clipping algorithm is any procedure that eliminates those portions of a picture outside

More information

Anoka Hennepin K-12 Curriculum plan

Anoka Hennepin K-12 Curriculum plan Anoka Hennepin K-12 Curriculum plan Department: Elementary Math Unit Title: Packages and Polygons (Blue Book, Geo and Measurement) Triangles and Beyond (Blue Book, Geo and Measurement) Everyday Math: Volume

More information

Mathematics 308 Geometry. Chapter 9. Drawing three dimensional objects

Mathematics 308 Geometry. Chapter 9. Drawing three dimensional objects Mathematics 308 Geometry Chapter 9. Drawing three dimensional objects In this chapter we will see how to draw three dimensional objects with PostScript. The task will be made easier by a package of routines

More information

You will have the entire period (until 9:00pm) to complete the exam, although the exam is designed to take less time.

You will have the entire period (until 9:00pm) to complete the exam, although the exam is designed to take less time. Page 1 of 6 Exam November 1, 2006 This exam is closed book and closed notes. You will have the entire period (until 9:00pm) to complete the exam, although the exam is designed to take less time. Please

More information

Computational Geometry Algorithmische Geometrie

Computational Geometry Algorithmische Geometrie Algorithmische Geometrie Panos Giannopoulos Wolfgang Mulzer Lena Schlipf AG TI SS 2013 !! Register in Campus Management!! Outline What you need to know (before taking this course) What is the course about?

More information

L1-Spatial Concepts L1 - Spatial Concepts

L1-Spatial Concepts L1 - Spatial Concepts L1 - Spatial Concepts NGEN06(TEK230) Algorithms in Geographical Information Systems Aim Understand the relationship between spatial queries and mathematical concepts. Know how topological relationships

More information

Lofting 3D Shapes. Abstract

Lofting 3D Shapes. Abstract Lofting 3D Shapes Robby Prescott Department of Computer Science University of Wisconsin Eau Claire Eau Claire, Wisconsin 54701 robprescott715@gmail.com Chris Johnson Department of Computer Science University

More information

CSCI 4620/8626. Coordinate Reference Frames

CSCI 4620/8626. Coordinate Reference Frames CSCI 4620/8626 Computer Graphics Graphics Output Primitives Last update: 2014-02-03 Coordinate Reference Frames To describe a picture, the world-coordinate reference frame (2D or 3D) must be selected.

More information

CS443: Digital Imaging and Multimedia Binary Image Analysis. Spring 2008 Ahmed Elgammal Dept. of Computer Science Rutgers University

CS443: Digital Imaging and Multimedia Binary Image Analysis. Spring 2008 Ahmed Elgammal Dept. of Computer Science Rutgers University CS443: Digital Imaging and Multimedia Binary Image Analysis Spring 2008 Ahmed Elgammal Dept. of Computer Science Rutgers University Outlines A Simple Machine Vision System Image segmentation by thresholding

More information

M. Andrea Rodríguez-Tastets. I Semester 2008

M. Andrea Rodríguez-Tastets. I Semester 2008 M. -Tastets Universidad de Concepción,Chile andrea@udec.cl I Semester 2008 Outline refers to data with a location on the Earth s surface. Examples Census data Administrative boundaries of a country, state

More information

Curve and Surface Basics

Curve and Surface Basics Curve and Surface Basics Implicit and parametric forms Power basis form Bezier curves Rational Bezier Curves Tensor Product Surfaces ME525x NURBS Curve and Surface Modeling Page 1 Implicit and Parametric

More information

Which n-venn diagrams can be drawn with convex k-gons?

Which n-venn diagrams can be drawn with convex k-gons? Which n-venn diagrams can be drawn with convex k-gons? Jeremy Carroll Frank Ruskey Mark Weston Abstract We establish a new lower bound for the number of sides required for the component curves of simple

More information

Acute Triangulations of Polygons

Acute Triangulations of Polygons Europ. J. Combinatorics (2002) 23, 45 55 doi:10.1006/eujc.2001.0531 Available online at http://www.idealibrary.com on Acute Triangulations of Polygons H. MAEHARA We prove that every n-gon can be triangulated

More information

morphology on binary images

morphology on binary images morphology on binary images Ole-Johan Skrede 10.05.2017 INF2310 - Digital Image Processing Department of Informatics The Faculty of Mathematics and Natural Sciences University of Oslo After original slides

More information

5 Graphs

5 Graphs 5 Graphs jacques@ucsd.edu Some of the putnam problems are to do with graphs. They do not assume more than a basic familiarity with the definitions and terminology of graph theory. 5.1 Basic definitions

More information

Applied Databases. Sebastian Maneth. Lecture 9 Spacial Queries and Indexes. University of Edinburgh - February 13th, 2017

Applied Databases. Sebastian Maneth. Lecture 9 Spacial Queries and Indexes. University of Edinburgh - February 13th, 2017 Applied Databases Lecture 9 Spacial Queries and Indexes Sebastian Maneth University of Edinburgh - February 13th, 2017 2 Outline 1. Assignment 2 2. Spatial Types 3. Spatial Queries 4. R-Trees 3 Assignment

More information

MA 323 Geometric Modelling Course Notes: Day 21 Three Dimensional Bezier Curves, Projections and Rational Bezier Curves

MA 323 Geometric Modelling Course Notes: Day 21 Three Dimensional Bezier Curves, Projections and Rational Bezier Curves MA 323 Geometric Modelling Course Notes: Day 21 Three Dimensional Bezier Curves, Projections and Rational Bezier Curves David L. Finn Over the next few days, we will be looking at extensions of Bezier

More information

Math 366 Lecture Notes Section 11.4 Geometry in Three Dimensions

Math 366 Lecture Notes Section 11.4 Geometry in Three Dimensions Math 366 Lecture Notes Section 11.4 Geometry in Three Dimensions Simple Closed Surfaces A simple closed surface has exactly one interior, no holes, and is hollow. A sphere is the set of all points at a

More information

Motion Planning. O Rourke, Chapter 8

Motion Planning. O Rourke, Chapter 8 O Rourke, Chapter 8 Outline Translating a polygon Moving a ladder Shortest Path (Point-to-Point) Goal: Given disjoint polygons in the plane, and given positions s and t, find the shortest path from s to

More information

CS3621 Midterm Solution (Fall 2005) 150 points

CS3621 Midterm Solution (Fall 2005) 150 points CS362 Midterm Solution Fall 25. Geometric Transformation CS362 Midterm Solution (Fall 25) 5 points (a) [5 points] Find the 2D transformation matrix for the reflection about the y-axis transformation (i.e.,

More information

5. Introduction to Procedures

5. Introduction to Procedures 5. Introduction to Procedures Topics: The module SimpleGraphics Creating and Showing figures Drawing Rectangles, Disks, and Stars Optional arguments Application Scripts Procedures We continue our introduction

More information

Beyond PostGIS. New developments in Open Source Spatial Databases. Karsten Vennemann. Seattle

Beyond PostGIS. New developments in Open Source Spatial Databases. Karsten Vennemann. Seattle New developments in Open Source Spatial Databases Karsten Vennemann Seattle Talk Overview Intro Relational Databases PostGIS JASPA INGRES Geospatial MySQL Spatial Support HatBox a user space extension

More information

Practical Linear Algebra: A Geometry Toolbox

Practical Linear Algebra: A Geometry Toolbox Practical Linear Algebra: A Geometry Toolbox Third edition Chapter 18: Putting Lines Together: Polylines and Polygons Gerald Farin & Dianne Hansford CRC Press, Taylor & Francis Group, An A K Peters Book

More information

Partitioning Orthogonal Polygons by Extension of All Edges Incident to Reflex Vertices: lower and upper bounds on the number of pieces

Partitioning Orthogonal Polygons by Extension of All Edges Incident to Reflex Vertices: lower and upper bounds on the number of pieces Partitioning Orthogonal Polygons by Extension of All Edges Incident to Reflex Vertices: lower and upper bounds on the number of pieces António Leslie Bajuelos 1, Ana Paula Tomás and Fábio Marques 3 1 Dept.

More information

Geometric Modeling Mortenson Chapter 11. Complex Model Construction

Geometric Modeling Mortenson Chapter 11. Complex Model Construction Geometric Modeling 91.580.201 Mortenson Chapter 11 Complex Model Construction Topics Topology of Models Connectivity and other intrinsic properties Graph-Based Models Emphasize topological structure Boolean

More information

2D rendering takes a photo of the 2D scene with a virtual camera that selects an axis aligned rectangle from the scene. The photograph is placed into

2D rendering takes a photo of the 2D scene with a virtual camera that selects an axis aligned rectangle from the scene. The photograph is placed into 2D rendering takes a photo of the 2D scene with a virtual camera that selects an axis aligned rectangle from the scene. The photograph is placed into the viewport of the current application window. A pixel

More information

Package geoops. March 19, 2018

Package geoops. March 19, 2018 Type Package Package geoops March 19, 2018 Title 'GeoJSON' Topology Calculations and Operations Tools for doing calculations and manipulations on 'GeoJSON', a 'geospatial' data interchange format ().

More information

Elementary Planar Geometry

Elementary Planar Geometry Elementary Planar Geometry What is a geometric solid? It is the part of space occupied by a physical object. A geometric solid is separated from the surrounding space by a surface. A part of the surface

More information

Scalar Field Visualization I

Scalar Field Visualization I Scalar Field Visualization I What is a Scalar Field? The approximation of certain scalar function in space f(x,y,z). Image source: blimpyb.com f What is a Scalar Field? The approximation of certain scalar

More information

Geometry Chapter 8 Test Review

Geometry Chapter 8 Test Review Geometry Chapter 8 Test Review Short Answer 1. Find the sum of the measures of the interior angles of the indicated convex polygon. Decagon 2. Find the sum of the measures of the interior angles of the

More information

Curriki Geometry Glossary

Curriki Geometry Glossary Curriki Geometry Glossary The following terms are used throughout the Curriki Geometry projects and represent the core vocabulary and concepts that students should know to meet Common Core State Standards.

More information

Geoapplications development Control work 1 (2017, Fall)

Geoapplications development Control work 1 (2017, Fall) Page 1 Geoapplications development Control work 1 (2017, Fall) Author: Antonio Rodriges, Oct. 2017 http://rgeo.wikience.org/ Surname, name, patronymic: Group: Date: Signature: Select all correct statements.

More information

Building Models. Objectives Introduce simple data structures for building polygonal models. Vertex lists Edge lists

Building Models. Objectives Introduce simple data structures for building polygonal models. Vertex lists Edge lists Building Models Objectives Introduce simple data structures for building polygonal models Vertex lists Edge lists 1 Representing a Mesh Consider a mesh v 5 v 6 e e e 3 v 9 8 8 v e 4 1 e 11 v e v 7 7 1

More information

Computational Geometry. Geometry Cross Product Convex Hull Problem Sweep Line Algorithm

Computational Geometry. Geometry Cross Product Convex Hull Problem Sweep Line Algorithm GEOMETRY COMP 321 McGill University These slides are mainly compiled from the following resources. - Professor Jaehyun Park slides CS 97SI - Top-coder tutorials. - Programming Challenges books. Computational

More information

Three applications of Euler s formula. Chapter 10

Three applications of Euler s formula. Chapter 10 Three applications of Euler s formula Chapter 10 A graph is planar if it can be drawn in the plane R without crossing edges (or, equivalently, on the -dimensional sphere S ). We talk of a plane graph if

More information

Grade 6 Math Circles February 19th/20th. Tessellations

Grade 6 Math Circles February 19th/20th. Tessellations Faculty of Mathematics Waterloo, Ontario N2L 3G1 Centre for Education in Mathematics and Computing Grade 6 Math Circles February 19th/20th Tessellations Introduction to Tessellations tessellation is a

More information

Lecture IV Bézier Curves

Lecture IV Bézier Curves Lecture IV Bézier Curves Why Curves? Why Curves? Why Curves? Why Curves? Why Curves? Linear (flat) Curved Easier More pieces Looks ugly Complicated Fewer pieces Looks smooth What is a curve? Intuitively:

More information

CS 325 Computer Graphics

CS 325 Computer Graphics CS 325 Computer Graphics 02 / 06 / 2012 Instructor: Michael Eckmann Today s Topics Questions? Comments? Antialiasing Polygons Interior points Fill areas tiling halftoning dithering Antialiasing Aliasing

More information

9. Three Dimensional Object Representations

9. Three Dimensional Object Representations 9. Three Dimensional Object Representations Methods: Polygon and Quadric surfaces: For simple Euclidean objects Spline surfaces and construction: For curved surfaces Procedural methods: Eg. Fractals, Particle

More information

EULER S FORMULA AND THE FIVE COLOR THEOREM

EULER S FORMULA AND THE FIVE COLOR THEOREM EULER S FORMULA AND THE FIVE COLOR THEOREM MIN JAE SONG Abstract. In this paper, we will define the necessary concepts to formulate map coloring problems. Then, we will prove Euler s formula and apply

More information

γ 2 γ 3 γ 1 R 2 (b) a bounded Yin set (a) an unbounded Yin set

γ 2 γ 3 γ 1 R 2 (b) a bounded Yin set (a) an unbounded Yin set γ 1 γ 3 γ γ 3 γ γ 1 R (a) an unbounded Yin set (b) a bounded Yin set Fig..1: Jordan curve representation of a connected Yin set M R. A shaded region represents M and the dashed curves its boundary M that

More information

Microsoft SQL Server CLR Types Serialization Formats

Microsoft SQL Server CLR Types Serialization Formats [MS-SSCLRT]: Intellectual Property Rights Notice for Open Specifications Documentation Technical Documentation. Microsoft publishes Open Specifications documentation for protocols, file formats, languages,

More information

Lecture overview. Visualisatie BMT. Fundamental algorithms. Visualization pipeline. Structural classification - 1. Structural classification - 2

Lecture overview. Visualisatie BMT. Fundamental algorithms. Visualization pipeline. Structural classification - 1. Structural classification - 2 Visualisatie BMT Fundamental algorithms Arjan Kok a.j.f.kok@tue.nl Lecture overview Classification of algorithms Scalar algorithms Vector algorithms Tensor algorithms Modeling algorithms 1 2 Visualization

More information

Package transformr. December 9, 2018

Package transformr. December 9, 2018 Type Package Title Polygon and Path Transformations Version 0.1.1 Date 2018-12-04 Package transformr December 9, 2018 Maintainer Thomas Lin Pedersen In order to smoothly animate the

More information

Intersection of an Oriented Box and a Cone

Intersection of an Oriented Box and a Cone Intersection of an Oriented Box and a Cone David Eberly, Geometric Tools, Redmond WA 98052 https://www.geometrictools.com/ This work is licensed under the Creative Commons Attribution 4.0 International

More information

HMMT February 2018 February 10, 2018

HMMT February 2018 February 10, 2018 HMMT February 2018 February 10, 2018 Combinatorics 1. Consider a 2 3 grid where each entry is one of 0, 1, and 2. For how many such grids is the sum of the numbers in every row and in every column a multiple

More information

The National Strategies Secondary Mathematics exemplification: Y8, 9

The National Strategies Secondary Mathematics exemplification: Y8, 9 Mathematics exemplification: Y8, 9 183 As outcomes, Year 8 pupils should, for example: Understand a proof that the sum of the angles of a triangle is 180 and of a quadrilateral is 360, and that the exterior

More information

SPACE - A Manifold Exploration Program

SPACE - A Manifold Exploration Program 1. Overview SPACE - A Manifold Exploration Program 1. Overview This appendix describes the manifold exploration program SPACE that is a companion to this book. Just like the GM program, the SPACE program

More information

Week 7 Convex Hulls in 3D

Week 7 Convex Hulls in 3D 1 Week 7 Convex Hulls in 3D 2 Polyhedra A polyhedron is the natural generalization of a 2D polygon to 3D 3 Closed Polyhedral Surface A closed polyhedral surface is a finite set of interior disjoint polygons

More information

Simultaneously flippable edges in triangulations

Simultaneously flippable edges in triangulations Simultaneously flippable edges in triangulations Diane L. Souvaine 1, Csaba D. Tóth 2, and Andrew Winslow 1 1 Tufts University, Medford MA 02155, USA, {dls,awinslow}@cs.tufts.edu 2 University of Calgary,

More information

Microsoft SQL Server CLR Types Serialization Formats

Microsoft SQL Server CLR Types Serialization Formats [MS-SSCLRT]: Intellectual Property Rights Notice for Open Specifications Documentation Technical Documentation. Microsoft publishes Open Specifications documentation for protocols, file formats, languages,

More information

TOWARDS A 3D SPATIAL QUERY LANGUAGE FOR BUILDING INFORMATION MODELS

TOWARDS A 3D SPATIAL QUERY LANGUAGE FOR BUILDING INFORMATION MODELS TOWARDS A D SPATIAL QUERY LANGUAGE FOR BUILDING INFORMATION MODELS André Borrmann 1, Christoph van Treeck 1, and Ernst Rank 1 ABSTRACT The paper introduces the concept of a spatial query language for building

More information

Standard 2.0 Knowledge of Geometry: Students will apply the properties of one-,

Standard 2.0 Knowledge of Geometry: Students will apply the properties of one-, VSC - Mathematics Print pages on legal paper, landscape mode. Grade PK Grade K Grade 1 Grade 2 Grade 3 Grade 4 Grade 5 Grade 6 Grade 7 Grade 8 Geometry: Students will apply the properties of one-, two-,

More information

Understanding and Working with the OGC Geopackage. Keith Ryden Lance Shipman

Understanding and Working with the OGC Geopackage. Keith Ryden Lance Shipman Understanding and Working with the OGC Geopackage Keith Ryden Lance Shipman Introduction - Introduction to Simple Features - What is the GeoPackage? - Esri Support - Looking ahead Geographic Things 3 Why

More information

Learning Task: Exploring Reflections and Rotations

Learning Task: Exploring Reflections and Rotations Learning Task: Exploring Reflections and Rotations Name Date Mathematical Goals Develop and demonstrate an understanding of reflections and rotations of figures in general and on a coordinate plane. Essential

More information

Glossary of dictionary terms in the AP geometry units

Glossary of dictionary terms in the AP geometry units Glossary of dictionary terms in the AP geometry units affine linear equation: an equation in which both sides are sums of terms that are either a number times y or a number times x or just a number [SlL2-D5]

More information

Chapter 8. Properties of Triangles and Quadrilaterals. 02/2017 LSowatsky

Chapter 8. Properties of Triangles and Quadrilaterals. 02/2017 LSowatsky Chapter 8 Properties of Triangles and Quadrilaterals 02/2017 LSowatsky 1 8-1A: Points, Lines, and Planes I can Identify and label basic geometric figures. LSowatsky 2 Vocabulary: Point: a point has no

More information

Acknowledgement: Scott, Foresman. Geometry. SIMILAR TRIANGLES. 1. Definition: A ratio represents the comparison of two quantities.

Acknowledgement: Scott, Foresman. Geometry. SIMILAR TRIANGLES. 1. Definition: A ratio represents the comparison of two quantities. 1 cknowledgement: Scott, Foresman. Geometry. SIMILR TRINGLS 1. efinition: ratio represents the comparison of two quantities. In figure, ratio of blue squares to white squares is 3 : 5 2. efinition: proportion

More information

Voronoi Diagrams in the Plane. Chapter 5 of O Rourke text Chapter 7 and 9 of course text

Voronoi Diagrams in the Plane. Chapter 5 of O Rourke text Chapter 7 and 9 of course text Voronoi Diagrams in the Plane Chapter 5 of O Rourke text Chapter 7 and 9 of course text Voronoi Diagrams As important as convex hulls Captures the neighborhood (proximity) information of geometric objects

More information

Graphics and Interaction Rendering pipeline & object modelling

Graphics and Interaction Rendering pipeline & object modelling 433-324 Graphics and Interaction Rendering pipeline & object modelling Department of Computer Science and Software Engineering The Lecture outline Introduction to Modelling Polygonal geometry The rendering

More information

Abstract We proved in this paper that 14 triangles are necessary to triangulate a square with every angle no more than 72, answering an unsolved probl

Abstract We proved in this paper that 14 triangles are necessary to triangulate a square with every angle no more than 72, answering an unsolved probl Acute Triangulation of Rectangles Yibin Zhang Hangzhou Foreign Languages School Xiaoyang Sun Hangzhou Foreign Languages School Zhiyuan Fan Hangzhou Xuejun High School 1 Advisor Dongbo Lu Hangzhou Foreign

More information

EXAMINATIONS 2016 TRIMESTER 2

EXAMINATIONS 2016 TRIMESTER 2 EXAMINATIONS 2016 TRIMESTER 2 CGRA 151 INTRODUCTION TO COMPUTER GRAPHICS Time Allowed: TWO HOURS CLOSED BOOK Permitted materials: Silent non-programmable calculators or silent programmable calculators

More information

Course Number: Course Title: Geometry

Course Number: Course Title: Geometry Course Number: 1206310 Course Title: Geometry RELATED GLOSSARY TERM DEFINITIONS (89) Altitude The perpendicular distance from the top of a geometric figure to its opposite side. Angle Two rays or two line

More information

THE LABELLED PEER CODE FOR KNOT AND LINK DIAGRAMS 26th February, 2015

THE LABELLED PEER CODE FOR KNOT AND LINK DIAGRAMS 26th February, 2015 THE LABELLED PEER CODE FOR KNOT AND LINK DIAGRAMS 26th February, 2015 A labelled peer code is a descriptive syntax for a diagram of a knot or link on a two dimensional sphere. The syntax is able to describe

More information

Tangencies between disjoint regions in the plane

Tangencies between disjoint regions in the plane June 16, 20 Problem Definition Two nonoverlapping Jordan regions in the plane are said to touch each other or to be tangent to each other if their boundaries have precisely one point in common and their

More information

We have set up our axioms to deal with the geometry of space but have not yet developed these ideas much. Let s redress that imbalance.

We have set up our axioms to deal with the geometry of space but have not yet developed these ideas much. Let s redress that imbalance. Solid geometry We have set up our axioms to deal with the geometry of space but have not yet developed these ideas much. Let s redress that imbalance. First, note that everything we have proven for the

More information

TWO CONTRIBUTIONS OF EULER

TWO CONTRIBUTIONS OF EULER TWO CONTRIBUTIONS OF EULER SIEMION FAJTLOWICZ. MATH 4315 Eulerian Tours. Although some mathematical problems which now can be thought of as graph-theoretical, go back to the times of Euclid, the invention

More information

Microsoft SQL Server CLR Types Serialization Formats

Microsoft SQL Server CLR Types Serialization Formats [MS-SSCLRT]: Intellectual Property Rights Notice for Open Specifications Documentation Technical Documentation. Microsoft publishes Open Specifications documentation for protocols, file formats, languages,

More information

Killingly Public Schools. Grades Draft Sept. 2002

Killingly Public Schools. Grades Draft Sept. 2002 Killingly Public Schools Grades 10-12 Draft Sept. 2002 ESSENTIALS OF GEOMETRY Grades 10-12 Language of Plane Geometry CONTENT STANDARD 10-12 EG 1: The student will use the properties of points, lines,

More information

3. Here is a stem and leaf plot of the Weights of students in East Junior High Algebra I Class

3. Here is a stem and leaf plot of the Weights of students in East Junior High Algebra I Class Test One Review Fall 06 Math 236 1. If a student budgets her money as indicated by this pie graph, how much of her weekly $170 goes to food? Expenses misc. 10% housing 20% housing 2. The following box

More information

Representing 2D Transformations as Matrices

Representing 2D Transformations as Matrices Representing 2D Transformations as Matrices John E. Howland Department of Computer Science Trinity University One Trinity Place San Antonio, Texas 78212-7200 Voice: (210) 999-7364 Fax: (210) 999-7477 E-mail:

More information

CS 763 F16. Moving objects in space with obstacles/constraints.

CS 763 F16. Moving objects in space with obstacles/constraints. Moving objects in space with obstacles/constraints. Objects = robots, vehicles, jointed linkages (robot arm), tools (e.g. on automated assembly line), foldable/bendable objects. Objects need not be physical

More information

TEACHER CERTIFICATION STUDY GUIDE KNOWLEDGE OF MATHEMATICS THROUGH SOLVING...1

TEACHER CERTIFICATION STUDY GUIDE KNOWLEDGE OF MATHEMATICS THROUGH SOLVING...1 TABLE OF CONTENTS COMPETENCY/SKILLS PG # COMPETENCY 1 KNOWLEDGE OF MATHEMATICS THROUGH PROBLEM SOLVING...1 Skill 1.1 Skill 1.2 Skill 1.3 Skill 1.4 Identify appropriate mathematical problems from real-world

More information

Unit 3 Transformations and Clipping

Unit 3 Transformations and Clipping Transformation Unit 3 Transformations and Clipping Changes in orientation, size and shape of an object by changing the coordinate description, is known as Geometric Transformation. Translation To reposition

More information

Derrick Stolee. April 12,

Derrick Stolee. April 12, 1 / 38 University Of Nebraska Lincoln Computer Science & Mathematics April 12, 2008 s-dstolee1@math.unl.edu 2 / 38 Acknowledgments Research Assistance and Funding This research funded by UCARE USDA FCIC/RMA

More information

arxiv: v1 [cs.cg] 2 Jul 2016

arxiv: v1 [cs.cg] 2 Jul 2016 Reversible Nets of Polyhedra Jin Akiyama 1, Stefan Langerman 2, and Kiyoko Matsunaga 1 arxiv:1607.00538v1 [cs.cg] 2 Jul 2016 1 Tokyo University of Science, 1-3 Kagurazaka, Shinjuku, Tokyo 162-8601, Japan

More information

Differential Geometry: Circle Patterns (Part 1) [Discrete Conformal Mappinngs via Circle Patterns. Kharevych, Springborn and Schröder]

Differential Geometry: Circle Patterns (Part 1) [Discrete Conformal Mappinngs via Circle Patterns. Kharevych, Springborn and Schröder] Differential Geometry: Circle Patterns (Part 1) [Discrete Conformal Mappinngs via Circle Patterns. Kharevych, Springborn and Schröder] Preliminaries Recall: Given a smooth function f:r R, the function

More information

3D graphics, raster and colors CS312 Fall 2010

3D graphics, raster and colors CS312 Fall 2010 Computer Graphics 3D graphics, raster and colors CS312 Fall 2010 Shift in CG Application Markets 1989-2000 2000 1989 3D Graphics Object description 3D graphics model Visualization 2D projection that simulates

More information

Computing NodeTrix Representations of Clustered Graphs

Computing NodeTrix Representations of Clustered Graphs Journal of Graph Algorithms and Applications http://jgaa.info/ vol. 22, no. 2, pp. 139 176 (2018) DOI: 10.7155/jgaa.00461 Computing NodeTrix Representations of Clustered Graphs Giordano Da Lozzo Giuseppe

More information

Combining Isometries- The Symmetry Group of a Square

Combining Isometries- The Symmetry Group of a Square Combining Isometries- The Symmetry Group of a Square L.A. Romero August 22, 2017 1 The Symmetry Group of a Square We begin with a definition. Definition 1.1. The symmetry group of a figure is the collection

More information

Package sfdct. August 29, 2017

Package sfdct. August 29, 2017 Package sfdct August 29, 2017 Title Constrained Triangulation for Simple Features Version 0.0.4 Build a constrained 'Delaunay' triangulation from simple features objects, applying constraints based on

More information

Boundary descriptors. Representation REPRESENTATION & DESCRIPTION. Descriptors. Moore boundary tracking

Boundary descriptors. Representation REPRESENTATION & DESCRIPTION. Descriptors. Moore boundary tracking Representation REPRESENTATION & DESCRIPTION After image segmentation the resulting collection of regions is usually represented and described in a form suitable for higher level processing. Most important

More information

Geometry. Zachary Friggstad. Programming Club Meeting

Geometry. Zachary Friggstad. Programming Club Meeting Geometry Zachary Friggstad Programming Club Meeting Points #i n c l u d e typedef complex p o i n t ; p o i n t p ( 1. 0, 5. 7 ) ; p. r e a l ( ) ; // x component p. imag ( ) ; // y component

More information