-- ================================== -- Module name: MyPrimitives -- Project: Foo -- Copyright (C) 2007 Bartosz Wójcik -- Created on: 01.10.2007 -- Last update: 28.11.2007 -- Version: % {- This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . -} -- ================================== module MyPrimitives where import Graphics.UI.GLUT import Graphics.Rendering.OpenGL -- Displays given primitive with given list of 2D vertices. -- displayPoints :: (Vertex (Vertex2 b)) => [(b, b)] -> PrimitiveMode -> IO () displayPoints points primitiveShape = do renderPrimitive primitiveShape $ mapM_ (\(x,y)->vertex$Vertex2 x y) points -- flush -- ========================================================================= -- Some functions creating and rendering circles in different configurations -- ========================================================================= -- Returns list of vertices that construct circle. -- Input - radius of circle and number of points constructing circle. -- More points - circle is more precise, but function takes more time to construct it. circlePoints :: (Floating a, Enum a) => a -> a -> [(a, a)] circlePoints radius number = [let alpha = 2*pi*i/number in (radius*(sin (alpha)) ,radius * (cos (alpha))) |i <- [1,2..number]] -- Returns list of vertices that construct circle of given radius. -- 64 points constructing circle were taken from experiment result. circle :: (Floating a, Enum a) => a -> [(a, a)] circle radius = circlePoints radius 64 -- Returns list of vertices that construct circle of given radius. -- 16 points constructing circle were taken from experiment result for small circles. circleSmall :: (Floating a, Enum a) => a -> [(a, a)] circleSmall radius = circlePoints radius 16 -- Displays circle of given radius -- renderCircle :: (Floating a, Enum a, Vertex (Vertex2 a)) => a -> IO () renderCircle r = displayPoints (circle r) LineLoop -- Displays filled circle of given radius fillCircle r = displayPoints (circle r) Polygon -- Displays filled small circle of given radius fillCircleSmall r = displayPoints (circleSmall r) Polygon -- Displays filled circle at given point -- filledCircleAt :: (Vertex (Vertex2 a), Enum a, Floating a) => GLfloat -> GLfloat -> a -> IO () filledCircleAt x y r = do translate$Vector3 x y (0::GLfloat) fillCircle r -- Displays filled circle at given point -- filledCircleAtV :: (Vertex (Vertex2 a), Enum a, Floating a) => (GLfloat, GLfloat) -> a -> IO () filledCircleAtV (x,y) r = filledCircleAt x y r