-- | -- Module : Graphics.Michelangelo.Shapes -- Description : -- Copyright : (c) Jonatan H Sundqvist, 2015 -- License : MIT -- Maintainer : Jonatan H Sundqvist -- Stability : experimental|stable -- Portability : -- -- Created July 30 2015 -- TODO | - Generic container types (eg. Monoids or OverloadedLists?) -- - Generic vertex types (?) -- - Anchored shapes (?) -- - Bounding boxes -- - Indexed shapes -- - Triangulation (or - more generally - tiling) of polygons -- - QuickCheck -- - Performance -- - Types to represent surfaces, edges, etc. -- SPEC | - -- - module Graphics.Michelangelo.Shapes where -------------------------------------------------------------------------------------------------------------------------------------------- -- We'll need these -------------------------------------------------------------------------------------------------------------------------------------------- -- import Data.Monoid import Graphics.Michelangelo.Types -------------------------------------------------------------------------------------------------------------------------------------------- -- Types -------------------------------------------------------------------------------------------------------------------------------------------- -- | A 'Face' is a list of vertices -- TODO: Polymorphic container -- TODO: Make sure all vertices lie in the same plane (using Triangles?) data Face v = Face [v] -- | data Edge v = Edge v v -------------------------------------------------------------------------------------------------------------------------------------------- -- Data -------------------------------------------------------------------------------------------------------------------------------------------- -- | TODO: Factor out π :: Floating f => f π = pi -------------------------------------------------------------------------------------------------------------------------------------------- -- Functions -------------------------------------------------------------------------------------------------------------------------------------------- -- Vertex constructors --------------------------------------------------------------------------------------------------------------------- -- | A simple list of vertices vlist :: a -> a -> a -> [a] vlist x y z = [x, y, z] -- Tessellation ---------------------------------------------------------------------------------------------------------------------------- -- Two-dimensional shapes ------------------------------------------------------------------------------------------------------------------ -- | Generate the vertices for a rectangular plane, centred at (0,0,0) plane :: Fractional f => (f -> f -> f -> a) -> f -> f -> f -> [a] plane f dx dy dz = [f (-dx/2) (dy/2) (dz/2), f (dx/2) (dy/2) (dz/2), f (dx/2) (-dy/2) (-dz/2), f (-dx/2) (-dy/2) (-dz/2)] -- | Generate the vertices for a rectangular plane, parallel with the X and Y axes and centred at (0,0,0) -- TODO: General 'plane' function planeXY :: Fractional f => (f -> f -> f -> a) -> f -> f -> [a] planeXY f dx dy = plane f dx dy 0 -- planeXY dx dy = [f (-dx/2) (dy/2) 0, f (dx/2) (dy/2) 0, f (dx/2) (-dy/2) 0, f (-dx/2) (-dy/2) 0] -- | Generate the vertices for a rectangular plane, parallel with the X and Z axes and centred at (0,0,0) -- TODO: General 'plane' function planeXZ :: Fractional f => (f -> f -> f -> a) -> f -> f -> [a] planeXZ f dx dz = plane f dx 0 dz -- | Generate the vertices for a rectangular plane, parallel with the Y and Z axes and centred at (0,0,0) -- TODO: General 'plane' function planeYZ :: Fractional f => (f -> f -> f -> a) -> f -> f -> [a] planeYZ f dy dz = plane f 0 dy dz -- | Generate the vertices for a regular polygon, centred at (0,0,0) polygon :: (Floating f, Integral i) => (f -> f -> a) -> i -> f -> [a] polygon f sides radius = [ let θ = fromIntegral n * 2*π/fromIntegral sides in f (radius*cos θ) (radius*sin θ) | n <- [0..(sides-1)] ] -- Three-dimensional shapes ---------------------------------------------------------------------------------------------------------------- -- | Generate the vertices of an axis-aligned cuboid centred at (0,0,0) -- TODO: Use combinatorics to generate vertices (?) cuboid :: Fractional f => (f -> f -> f -> a) -> f -> f -> f -> [[a]] cuboid f dx dy dz = [[f (-hdx) hdy hdz, f hdx hdy hdz, f hdx hdy (-hdz), f (-hdx) hdy (-hdz)], [f (-hdx) (-hdy) hdz, f hdx (-hdy) hdz, f hdx (-hdy) (-hdz), f (-hdx) (-hdy) (-hdz)]] where (hdx, hdy, hdz) = (dx/2, dy/2, dz/2) -- | Generate the vertices of an axis-aligned cube centred at (0,0,0) cube :: Fractional f => (f -> f -> f -> a) -> f -> [[a]] cube f side = cuboid f side side side