Skip to content

Commit

Permalink
More documentation...
Browse files Browse the repository at this point in the history
  • Loading branch information
colah committed Aug 20, 2012
1 parent 15e88c2 commit 85960e9
Show file tree
Hide file tree
Showing 2 changed files with 101 additions and 12 deletions.
102 changes: 90 additions & 12 deletions Graphics/Implicit/Export/Render/GetSegs.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,16 +6,51 @@ module Graphics.Implicit.Export.Render.GetSegs where
import Graphics.Implicit.Definitions
import Graphics.Implicit.Export.Render.RefineSegs (refine)

{-- # INLINE getSegs' #-}

getSegs' (x1, y1) (x2, y2) obj (midx1V,midx2V,midy1V,midy2V) =
let
x1y1 = obj (x1, y1)
x2y1 = obj (x2, y1)
x1y2 = obj (x1, y2)
x2y2 = obj (x2, y2)
in
getSegs (x1, y1) (x2, y2) obj (x1y1, x2y1, x1y2, x2y2) (midx1V,midx2V,midy1V,midy2V)
{- The goal of getSegs is to create polylines to separate
the interior and exterior vertices of a square intersectiong
an object described by an implicit function.
O.....O O.....O
: : : :
: * : ,--*
* : => *-- :
: : : :
#.....# #.....#
An interior point is one at which obj is negative.
What are all the variables?
===========================
To allow data sharing, lots of values we
could calculate are instead arguments.
positions obj values
--------- ----------
(x1,y2) .. (x2,y2) obj x1y2 .. x2y2
: : => : :
(x1,y1) .. (x2,y1) x1y1 .. x2y2
mid points
----------
(midy2V, y2)
= midy2
......*.....
: :
(x1, midx1V) * * (x2, midx2V)
= midx1 : : = midx2
:....*.....:
(midy1V, y1)
= midy1
-}

getSegs :: ℝ2 -> ℝ2 -> Obj2 -> (,,,) -> (,,,) -> [Polyline]
{-- # INLINE getSegs #-}
Expand All @@ -38,45 +73,88 @@ getSegs (x1, y1) (x2, y2) obj (x1y1, x2y1, x1y2, x2y2) (midx1V,midx2V,midy1V,mid

notPointLine (p1:p2:[]) = p1 /= p2

-- takes straight lines between mid points and subdivides them to
-- account for sharp corners, etc.

in map (refine res obj) . filter (notPointLine) $ case (x1y2 <= 0, x2y2 <= 0,
x1y1 <= 0, x2y1 <= 0) of
x1y1 <= 0, x2y1 <= 0) of

-- An important point here is orientation. If you imagine going along a
-- generated segment, the interior should be on the left-hand side.

-- Empty Cases

-- Yes, there's some symetries that could reduce the amount of code...
-- But I don't think they're worth exploiting...
(True, True,
True, True) -> []

(False, False,
False, False) -> []

-- Horizontal Cases

(True, True,
False, False) -> [[midx1, midx2]]

(False, False,
True, True) -> [[midx2, midx1]]

-- Vertical Cases

(False, True,
False, True) -> [[midy2, midy1]]

(True, False,
True, False) -> [[midy1, midy2]]

-- Corner Cases

(True, False,
False, False) -> [[midx1, midy2]]

(False, True,
True, True) -> [[midy2, midx1]]

(True, True,
False, True) -> [[midx1, midy1]]

(False, False,
True, False) -> [[midy1, midx1]]

(True, True,
True, False) -> [[midy1, midx2]]

(False, False,
False, True) -> [[midx2, midy1]]

(True, False,
True, True) -> [[midx2, midy2]]

(False, True,
False, False) -> [[midy2, midx2]]

-- Dual Corner Cases

(True, False,
False, True) -> if c <= 0
then [[midx1, midy1], [midx2, midy2]]
else [[midx1, midy2], [midx2, midy1]]

(False, True,
True, False) -> if c <= 0
then [[midy2, midx1], [midy1, midx2]]
else [[midy1, midx1], [midy2, midx2]]


-- A convenience function, we don't actually care too much about

{-- # INLINE getSegs' #-}

getSegs' (x1, y1) (x2, y2) obj (midx1V,midx2V,midy1V,midy2V) =
let
x1y1 = obj (x1, y1)
x2y1 = obj (x2, y1)
x1y2 = obj (x1, y2)
x2y2 = obj (x2, y2)
in
getSegs (x1, y1) (x2, y2) obj (x1y1, x2y1, x1y2, x2y2) (midx1V,midx2V,midy1V,midy2V)

11 changes: 11 additions & 0 deletions Graphics/Implicit/Export/Render/RefineSegs.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,14 +7,25 @@ import Graphics.Implicit.Definitions
import qualified Graphics.Implicit.SaneOperators as S
import Graphics.Implicit.SaneOperators ((⋅), (⨯), norm, normalized)

-- The purpose of refine is to add detail to a polyline aproximating
-- the boundary of an implicit function and to remove redundant points.

refine :: -> Obj2 -> [ℝ2] -> [ℝ2]

-- We break this into two steps: detail and then simplify.

refine res obj = simplify res . detail' res obj

-- we wrap detail to make it ignore very small segments, and to pass in
-- an initial value for a pointer counter argument. This is detail'


detail' res obj [p1@(x1,y1), p2@(x2,y2)] | (x2-x1)^2 + (y2-y1)^2 > res^2/200 =
detail 0 res obj [p1,p2]
detail' _ _ a = a

-- detail adds new points to a polyline to add more detail.

detail :: Int -> -> (ℝ2 -> ) -> [ℝ2] -> [ℝ2]
detail n res obj [p1@(x1,y1), p2@(x2,y2)] | n < 2 =
let
Expand Down

0 comments on commit 85960e9

Please sign in to comment.