DIAG: consistently use [[PT]] for all Diags
Also simplify a few things like needless strokeTrail usage.
This commit is contained in:
parent
f16fe7738a
commit
f8fb61e80a
@ -15,26 +15,23 @@ import Diagrams.Prelude hiding ((<>))
|
|||||||
import Diagrams.TwoD.Layout.Tree
|
import Diagrams.TwoD.Layout.Tree
|
||||||
import Graphics.Diagram.Core
|
import Graphics.Diagram.Core
|
||||||
import Parser.PathParser
|
import Parser.PathParser
|
||||||
|
import Safe
|
||||||
|
|
||||||
|
|
||||||
-- |Draw the lines of the polygon.
|
-- |Draw the lines of the polygon.
|
||||||
polyLines :: Diag
|
polyLines :: Diag
|
||||||
polyLines = Diag f
|
polyLines = Diag f
|
||||||
where
|
where
|
||||||
f _ [] = mempty
|
f _ = foldl (\x y -> x <> strokePoly y) mempty
|
||||||
f _ (x:y:_) =
|
|
||||||
strokePoly x <> strokePoly y
|
|
||||||
where
|
where
|
||||||
strokePoly x' = (strokeTrail . fromVertices $ x' ++ [head x'])
|
strokePoly x' = fromVertices $ x' ++ (maybeToList . headMay $ x')
|
||||||
# moveTo (head x') # lc black
|
|
||||||
f _ _ = mempty
|
|
||||||
|
|
||||||
|
|
||||||
-- |Show the intersection points of two polygons as red dots.
|
-- |Show the intersection points of two polygons as red dots.
|
||||||
polyIntersection :: Diag
|
polyIntersection :: Diag
|
||||||
polyIntersection = Diag f
|
polyIntersection = Diag f
|
||||||
where
|
where
|
||||||
f p (x:y:_) = drawP vtpi (dotSize p) # fc red # lc red
|
f p [x, y] = drawP vtpi (dotSize p) # fc red # lc red
|
||||||
where
|
where
|
||||||
vtpi = intersectionPoints . sortLexPolys $ (sortLexPoly x, sortLexPoly y)
|
vtpi = intersectionPoints . sortLexPolys $ (sortLexPoly x, sortLexPoly y)
|
||||||
f _ _ = mempty
|
f _ _ = mempty
|
||||||
@ -44,7 +41,7 @@ polyIntersection = Diag f
|
|||||||
polyIntersectionText :: Diag
|
polyIntersectionText :: Diag
|
||||||
polyIntersectionText = Diag f
|
polyIntersectionText = Diag f
|
||||||
where
|
where
|
||||||
f p (x:y:_)
|
f p [x, y]
|
||||||
| showCoordText p = position . zip vtpi $ (pointToTextCoord # fc red <$> vtpi)
|
| showCoordText p = position . zip vtpi $ (pointToTextCoord # fc red <$> vtpi)
|
||||||
# translate (r2 (0, 10))
|
# translate (r2 (0, 10))
|
||||||
| otherwise = mempty
|
| otherwise = mempty
|
||||||
@ -60,21 +57,20 @@ polyIntersectionText = Diag f
|
|||||||
convexHP :: Diag
|
convexHP :: Diag
|
||||||
convexHP = Diag f
|
convexHP = Diag f
|
||||||
where
|
where
|
||||||
f p [vt] = drawP (grahamCH vt) (dotSize p) # fc red # lc red
|
f p vts = drawP (grahamCH (concat vts)) (dotSize p) # fc red # lc red
|
||||||
f _ _ = mempty
|
|
||||||
|
|
||||||
|
|
||||||
-- |Show coordinates as text above the convex hull points.
|
-- |Show coordinates as text above the convex hull points.
|
||||||
convexHPText :: Diag
|
convexHPText :: Diag
|
||||||
convexHPText = Diag f
|
convexHPText = Diag f
|
||||||
where
|
where
|
||||||
f p [vt]
|
f p vts
|
||||||
| showCoordText p =
|
| showCoordText p =
|
||||||
position $ zip vtchf (pointToTextCoord <$> vtchf) # translate (r2 (0, 10))
|
(position . zip vtch $ (pointToTextCoord <$> vtch))
|
||||||
|
# translate (r2 (0, 10))
|
||||||
| otherwise = mempty
|
| otherwise = mempty
|
||||||
where
|
where
|
||||||
vtchf = grahamCH vt
|
vtch = grahamCH (concat vts)
|
||||||
f _ _ = mempty
|
|
||||||
|
|
||||||
|
|
||||||
-- |Create a diagram which shows the lines along the convex hull
|
-- |Create a diagram which shows the lines along the convex hull
|
||||||
@ -82,10 +78,14 @@ convexHPText = Diag f
|
|||||||
convexHLs :: Diag
|
convexHLs :: Diag
|
||||||
convexHLs = Diag f
|
convexHLs = Diag f
|
||||||
where
|
where
|
||||||
f _ [vt] =
|
f _ vts =
|
||||||
(strokeTrail . fromVertices . flip (++) [head $ grahamCH vt] . grahamCH $ vt)
|
(fromVertices
|
||||||
# moveTo (head $ grahamCH vt) # lc red
|
. flip (++) (maybeToList . headMay . grahamCH $ vt)
|
||||||
f _ _ = mempty
|
. grahamCH
|
||||||
|
$ vt
|
||||||
|
) # lc red
|
||||||
|
where
|
||||||
|
vt = mconcat vts
|
||||||
|
|
||||||
|
|
||||||
-- |Create list of diagrama which describe the lines along points of a half
|
-- |Create list of diagrama which describe the lines along points of a half
|
||||||
@ -94,9 +94,7 @@ convexHLs = Diag f
|
|||||||
convexHStepsLs :: Diag
|
convexHStepsLs :: Diag
|
||||||
convexHStepsLs = GifDiag f
|
convexHStepsLs = GifDiag f
|
||||||
where
|
where
|
||||||
f _ col g vt = fmap mkChDiag (g vt)
|
f _ col g vt = fmap (\x -> fromVertices x # lc col) (g vt)
|
||||||
where
|
|
||||||
mkChDiag vt' = (strokeTrail . fromVertices $ vt') # moveTo (head vt') # lc col
|
|
||||||
|
|
||||||
|
|
||||||
-- |Create a diagram that shows all squares of the RangeSearch algorithm
|
-- |Create a diagram that shows all squares of the RangeSearch algorithm
|
||||||
@ -104,24 +102,23 @@ convexHStepsLs = GifDiag f
|
|||||||
squares :: Diag
|
squares :: Diag
|
||||||
squares = Diag f
|
squares = Diag f
|
||||||
where
|
where
|
||||||
f p [vt] =
|
f p vts =
|
||||||
mconcat
|
mconcat
|
||||||
$ (uncurry rectByDiagonal # lw ultraThin)
|
$ (uncurry rectByDiagonal # lw ultraThin)
|
||||||
<$>
|
<$>
|
||||||
(quadTreeSquares (xDimension p, yDimension p)
|
(quadTreeSquares (xDimension p, yDimension p)
|
||||||
. quadTree vt
|
. quadTree (mconcat vts)
|
||||||
$ (xDimension p, yDimension p))
|
$ (xDimension p, yDimension p))
|
||||||
f _ _ = mempty
|
|
||||||
|
|
||||||
|
|
||||||
-- |Draw the squares of the kd-tree.
|
-- |Draw the squares of the kd-tree.
|
||||||
kdSquares :: Diag
|
kdSquares :: Diag
|
||||||
kdSquares = Diag f
|
kdSquares = Diag f
|
||||||
where
|
where
|
||||||
f p [vt] =
|
f p vts =
|
||||||
mconcat
|
mconcat
|
||||||
. fmap (uncurry (~~))
|
. fmap (uncurry (~~))
|
||||||
$ kdLines (kdTree vt Horizontal) (xDimension p, yDimension p)
|
$ kdLines (kdTree (mconcat vts) Horizontal) (xDimension p, yDimension p)
|
||||||
where
|
where
|
||||||
-- Gets all lines that make up the kdSquares. Every line is
|
-- Gets all lines that make up the kdSquares. Every line is
|
||||||
-- described by two points, start and end respectively.
|
-- described by two points, start and end respectively.
|
||||||
@ -141,26 +138,26 @@ kdSquares = Diag f
|
|||||||
where
|
where
|
||||||
(_, y') = unp2 pt
|
(_, y') = unp2 pt
|
||||||
kdLines _ _ = []
|
kdLines _ _ = []
|
||||||
f _ _ = mempty
|
|
||||||
|
|
||||||
|
|
||||||
-- |Draw the range rectangle and highlight the points inside that range.
|
-- |Draw the range rectangle and highlight the points inside that range.
|
||||||
kdRange :: Diag
|
kdRange :: Diag
|
||||||
kdRange = Diag f
|
kdRange = Diag f
|
||||||
where
|
where
|
||||||
f p [vt] =
|
f p vts =
|
||||||
(uncurry rectByDiagonal # lc red) (rangeSquare p)
|
(uncurry rectByDiagonal # lc red) (rangeSquare p)
|
||||||
<> drawP ptsInRange (dotSize p) # fc red # lc red
|
<> drawP ptsInRange (dotSize p) # fc red # lc red
|
||||||
where
|
where
|
||||||
ptsInRange = fst . rangeSearch (kdTree vt Vertical) $ rangeSquare p
|
ptsInRange = fst
|
||||||
f _ _ = mempty
|
. rangeSearch (kdTree (mconcat vts) Vertical)
|
||||||
|
$ rangeSquare p
|
||||||
|
|
||||||
|
|
||||||
-- |The kd-tree visualized as binary tree.
|
-- |The kd-tree visualized as binary tree.
|
||||||
kdTreeDiag :: Diag
|
kdTreeDiag :: Diag
|
||||||
kdTreeDiag = Diag f
|
kdTreeDiag = Diag f
|
||||||
where
|
where
|
||||||
f p [vt] =
|
f p vts =
|
||||||
-- HACK: in order to give specific nodes a specific color
|
-- HACK: in order to give specific nodes a specific color
|
||||||
renderTree (\n -> case n of
|
renderTree (\n -> case n of
|
||||||
'*':'*':_ -> (text n # fontSizeL 5.0)
|
'*':'*':_ -> (text n # fontSizeL 5.0)
|
||||||
@ -174,10 +171,9 @@ kdTreeDiag = Diag f
|
|||||||
# scale 2 # alignT # bg white
|
# scale 2 # alignT # bg white
|
||||||
where
|
where
|
||||||
roseTree = snd
|
roseTree = snd
|
||||||
. rangeSearch (kdTree vt Vertical)
|
. rangeSearch (kdTree (mconcat vts) Vertical)
|
||||||
$ rangeSquare p
|
$ rangeSquare p
|
||||||
|
|
||||||
f _ _ = mempty
|
|
||||||
|
|
||||||
|
|
||||||
-- |Get the quad tree corresponding to the given points and diagram properties.
|
-- |Get the quad tree corresponding to the given points and diagram properties.
|
||||||
@ -190,16 +186,15 @@ qt vt p = quadTree vt (xDimension p, yDimension p)
|
|||||||
quadPathSquare :: Diag
|
quadPathSquare :: Diag
|
||||||
quadPathSquare = Diag f
|
quadPathSquare = Diag f
|
||||||
where
|
where
|
||||||
f p [vt] =
|
f p vts =
|
||||||
(uncurry rectByDiagonal # lw thin # lc red)
|
(uncurry rectByDiagonal # lw thin # lc red)
|
||||||
(getSquare (stringToQuads (quadPath p)) (qt vt p, []))
|
(getSquare (stringToQuads (quadPath p)) (qt (mconcat vts) p, []))
|
||||||
where
|
where
|
||||||
getSquare :: [Either Quad Orient] -> QTZipper PT -> Square
|
getSquare :: [Either Quad Orient] -> QTZipper PT -> Square
|
||||||
getSquare [] z = getSquareByZipper (xDimension p, yDimension p) z
|
getSquare [] z = getSquareByZipper (xDimension p, yDimension p) z
|
||||||
getSquare (q:qs) z = case q of
|
getSquare (q:qs) z = case q of
|
||||||
Right x -> getSquare qs (fromMaybe z (findNeighbor x z))
|
Right x -> getSquare qs (fromMaybe z (findNeighbor x z))
|
||||||
Left x -> getSquare qs (fromMaybe z (goQuad x z))
|
Left x -> getSquare qs (fromMaybe z (goQuad x z))
|
||||||
f _ _ = mempty
|
|
||||||
|
|
||||||
|
|
||||||
-- |Create a list of diagrams that show the walk along the given path
|
-- |Create a list of diagrams that show the walk along the given path
|
||||||
@ -224,9 +219,9 @@ gifQuadPath = GifDiag f
|
|||||||
treePretty :: Diag
|
treePretty :: Diag
|
||||||
treePretty = Diag f
|
treePretty = Diag f
|
||||||
where
|
where
|
||||||
f p [vt] =
|
f p vts =
|
||||||
prettyRoseTree (quadTreeToRoseTree
|
prettyRoseTree (quadTreeToRoseTree
|
||||||
. flip getCurQT (qt vt p, [])
|
. flip getCurQT (qt (mconcat vts) p, [])
|
||||||
. stringToQuads
|
. stringToQuads
|
||||||
. quadPath
|
. quadPath
|
||||||
$ p)
|
$ p)
|
||||||
@ -247,4 +242,3 @@ treePretty = Diag f
|
|||||||
(~~)
|
(~~)
|
||||||
(symmLayout' (with & slHSep .~ 60 & slVSep .~ 40) tree)
|
(symmLayout' (with & slHSep .~ 60 & slVSep .~ 40) tree)
|
||||||
# scale 2 # alignT # bg white
|
# scale 2 # alignT # bg white
|
||||||
f _ _ = mempty
|
|
||||||
|
@ -54,13 +54,21 @@ diag p das vts = maybe mempty (\x -> mkDiag x p vts)
|
|||||||
-- |Create the Diagram from a String which is supposed to be the contents
|
-- |Create the Diagram from a String which is supposed to be the contents
|
||||||
-- of an obj file.
|
-- of an obj file.
|
||||||
diagS :: DiagProp -> B.ByteString -> Diagram Cairo R2
|
diagS :: DiagProp -> B.ByteString -> Diagram Cairo R2
|
||||||
diagS p mesh
|
diagS p mesh =
|
||||||
| algo p == 2 || algo p == 3 =
|
diag p diagAlgos
|
||||||
diag p diagAlgos . fmap (filterValidPT p) . facesToArr $ mesh
|
. fmap (filterValidPT p)
|
||||||
| otherwise = diag p diagAlgos . (: []) . filterValidPT p . meshToArr $ mesh
|
. (\x -> if null x then [meshToArr mesh] else x)
|
||||||
|
. facesToArr
|
||||||
|
$ mesh
|
||||||
|
|
||||||
|
|
||||||
-- |Create the tree diagram from a String which is supposed to be the contents
|
-- |Create the tree diagram from a String which is supposed to be the contents
|
||||||
-- of an obj file.
|
-- of an obj file.
|
||||||
diagTreeS :: DiagProp -> B.ByteString -> Diagram Cairo R2
|
diagTreeS :: DiagProp -> B.ByteString -> Diagram Cairo R2
|
||||||
diagTreeS p = diag p diagTreAlgos . (: []) . filterValidPT p . meshToArr
|
diagTreeS p mesh =
|
||||||
|
diag p diagTreAlgos
|
||||||
|
. fmap (filterValidPT p)
|
||||||
|
. (\x -> if null x then [meshToArr mesh] else x)
|
||||||
|
. facesToArr
|
||||||
|
$ mesh
|
||||||
|
|
||||||
|
@ -13,8 +13,6 @@ import Graphics.Diagram.Core
|
|||||||
coordPoints :: Diag
|
coordPoints :: Diag
|
||||||
coordPoints = Diag f
|
coordPoints = Diag f
|
||||||
where
|
where
|
||||||
f _ [] = mempty
|
|
||||||
f p [vt] = drawP vt (dotSize p) # fc black # lc black
|
|
||||||
f p vts = drawP (concat vts) (dotSize p) # fc black # lc black
|
f p vts = drawP (concat vts) (dotSize p) # fc black # lc black
|
||||||
|
|
||||||
|
|
||||||
@ -22,8 +20,6 @@ coordPoints = Diag f
|
|||||||
coordPointsText :: Diag
|
coordPointsText :: Diag
|
||||||
coordPointsText = Diag f
|
coordPointsText = Diag f
|
||||||
where
|
where
|
||||||
f _ [] = mempty
|
|
||||||
f p [vt] = drawT vt p
|
|
||||||
f p vts = drawT (concat vts) p
|
f p vts = drawT (concat vts) p
|
||||||
drawT [] _ = mempty
|
drawT [] _ = mempty
|
||||||
drawT vt p
|
drawT vt p
|
||||||
|
Loading…
Reference in New Issue
Block a user