diff --git a/Diagram.hs b/Diagram.hs index 241ce17..70e7f5e 100644 --- a/Diagram.hs +++ b/Diagram.hs @@ -21,7 +21,7 @@ import Parser.Meshparser -- coordinates and common properties. data Diag = Diag { mkDiag :: DiagProp - -> VTable + -> [PT] -> Diagram Cairo R2 } @@ -31,9 +31,9 @@ data DiagProp = MkProp { -- |The thickness of the dots. t :: Double, -- |The dimensions of the x-axis. - dX :: (Double, Double), + dX :: Coord, -- |The dimensions of the y-axis. - dY :: (Double, Double), + dY :: Coord, -- |Algorithm to use. alg :: Int } @@ -95,13 +95,11 @@ showCoordinates :: Diag showCoordinates = Diag f where f p vt - = position (zip (map mkPoint . filter (inRange (dX p) (dY p)) $ vt) + = position (zip (filter (inRange (dX p) (dY p)) $ vt) (repeat dot)) # moveTo (p2(xOffset p, yOffset p)) where -- a dot itself is a diagram dot = (circle $ t p :: Diagram Cairo R2) # fc black - -- this is just abstraction - mkPoint (x,y) = p2 (x,y) -- |Creates a Diagram that shows an XAxis which is bound @@ -129,7 +127,7 @@ showWhiteRectB = Diag f -- |Create the Diagram from the VTable. -diag :: DiagProp -> VTable -> Diagram Cairo R2 +diag :: DiagProp -> [PT] -> Diagram Cairo R2 diag p = case alg p of 0 -> mkDiag (mconcat [showCoordinates, showXAxis, showYAxis, showWhiteRectB]) @@ -141,7 +139,7 @@ diag p = case alg p of -- of an obj file. diagS :: DiagProp -> String -> Diagram Cairo R2 diagS p mesh - = diag p . + = diag p . meshToArr $ mesh diff --git a/LinearAlgebra/Vector.hs b/LinearAlgebra/Vector.hs index 80808ac..f4ce09a 100644 --- a/LinearAlgebra/Vector.hs +++ b/LinearAlgebra/Vector.hs @@ -2,26 +2,74 @@ module LinearAlgebra.Vector where -import Data.Vector.Class +import Diagrams.TwoD.Types + +type Vec = R2 +type PT = P2 +type Coord = (Double, Double) -type Angle = Double - - --- |Checks whether the Coordinates are in a given dimension. -inRange :: (Double, Double) -- ^ X dimension - -> (Double, Double) -- ^ Y dimension - -> (Double, Double) -- ^ Coordinates - -> Bool -- ^ result -inRange (xlD, xuD) (ylD, yuD) (x,y) +-- |Checks whether the Point is in a given dimension. +inRange :: Coord -- ^ X dimension + -> Coord -- ^ Y dimension + -> PT -- ^ Coordinates + -> Bool -- ^ result +inRange (xlD, xuD) (ylD, yuD) p = x <= xuD && x >= xlD && y <= yuD && y >= ylD + where + (x, y) = unp2 p -- |Get the angle between two vectors in degrees. -getAngle :: (Vector v) => v -> v -> Angle -getAngle a b = (*) 180.0 . - flip (/) pi . - acos . - flip (/) (vmag a * vmag b) . - vdot a $ +getAngle :: Vec -> Vec -> Double +getAngle a b = acos . + flip (/) (vecLength a * vecLength b) . + scalarProd a $ b + + +-- |Get the length of a vector. +vecLength :: Vec -> Double +vecLength v = sqrt (x^2 + y^2) + where + (x, y) = unr2 v + + +-- |Compute the scalar product of two vectors. +scalarProd :: Vec -> Vec -> Double +scalarProd v1 v2 = a1 * b1 + a2 * b2 + where + (a1, a2) = unr2 v1 + (b1, b2) = unr2 v2 + + +-- |Construct a vector that points to a point from the origin. +pt2Vec :: PT -> Vec +pt2Vec = r2 . unp2 + + +-- |Give the point which is at the coordinates the vector +-- points to from the origin. +vec2Pt :: Vec -> PT +vec2Pt = p2 . unr2 + + +-- |Construct a vector between two points. +vp2 :: PT -- ^ vector origin + -> PT -- ^ vector points here + -> Vec +vp2 a b = (pt2Vec b) - (pt2Vec a) + + +-- |Checks if 3 points a,b,c build a counterclock wise triangle by +-- connecting a-b-c. This is done by computing thed determinant and +-- checking the algebraic sign. +ccw :: PT -> PT -> PT -> Bool +ccw a b c = (bx - ax) * + (cy - ay) - + (by - ay) * + (cx - ax) >= 0 + where + (ax, ay) = unp2 a + (bx, by) = unp2 b + (cx, cy) = unp2 c diff --git a/Parser/Meshparser.hs b/Parser/Meshparser.hs index 3428541..7adf8c3 100644 --- a/Parser/Meshparser.hs +++ b/Parser/Meshparser.hs @@ -1,23 +1,25 @@ {-# OPTIONS_HADDOCK ignore-exports #-} -module Parser.Meshparser (VTable, meshToArr) where +module Parser.Meshparser (meshToArr) where import Control.Applicative +import Diagrams.TwoD.Types +import LinearAlgebra.Vector import Parser.Core --- |The VTable is represented by a 'Double' tuple, 2-dimensional. -type VTable = [(Double, Double)] -- | Convert a text String with multiple vertices into -- an array of float tuples. meshToArr :: String -- ^ the string to convert - -> VTable -- ^ the resulting vertice table -meshToArr xs = fmap (\(Just (x, _)) -> x) . + -> [PT] -- ^ the resulting vertice table +meshToArr xs = fmap (p2) . + fmap (\(Just (x, _)) -> x) . filter (/= Nothing) . fmap (runParser parseVertice) . lines $ xs + -- | Creates a Parser that accepts a single vertice, such as 'v 1.0 2.0'. parseVertice :: Parser (Double, Double) parseVertice = (,) <$>