diagrams-contrib-1.4.0.1: Collection of user contributions to diagrams EDSL

Safe HaskellNone
LanguageHaskell2010

Diagrams.TwoD.Path.Boolean

Contents

Description

Set operations on paths. As a side effect it removes overlapping regions. Since Path is TrailLike, you can use these operations directly with any combinator which generates Loops, like circle or fromSegments. Lines are discarded, only Loops are used. If you have several paths, you can combine them with <> first. Use toPath if you want to convert a Trail or Located Trail to a Path. The FillRule argument determines how insideness is calculated for the input.

Synopsis

Operations on Paths

union :: FillRule -> Path V2 Double -> Path V2 Double Source #

Remove overlapping regions in the path. If you have several paths, combine them using <> first.

import Diagrams.TwoD.Path.Boolean
import Diagrams.Prelude hiding (union)

unionEx = frame 0.1 . strokePath $ union Winding $
          (square 1) <> circle 0.5 # translate (V2 0.5 (-0.5))

difference :: FillRule -> Path V2 Double -> Path V2 Double -> Path V2 Double Source #

Difference of two paths. First overlap is removed in the two input arguments, then the difference is calculated.

import Diagrams.TwoD.Path.Boolean
import Diagrams.Prelude hiding (difference)

diffEx = frame 0.1 . strokePath $
         difference Winding (square 1) $
         circle 0.5 # translate (V2 0.5 (-0.5))

intersection :: FillRule -> Path V2 Double -> Path V2 Double -> Path V2 Double Source #

Intersection of two paths. First overlap is removed in the two input arguments, then the intersection is calculated.

import Diagrams.TwoD.Path.Boolean
import Diagrams.Prelude hiding (intersection)

isectEx = frame 0.1 . strokePath $
          intersection Winding (square 1) $
          circle 0.5 # translate (V2 0.5 (-0.5))

exclusion :: FillRule -> Path V2 Double -> Path V2 Double -> Path V2 Double Source #

Exclusion (exclusive or) of two paths. First overlap is removed in the two input arguments, then the exclusion is calculated.

import Diagrams.TwoD.Path.Boolean

exclEx = fc grey . frame 0.1 . strokePath $
         exclusion Winding (square 1) $
         circle 0.5 # translate (V2 0.5 (-0.5))

Operations on Paths with tolerance

union' :: Double -> FillRule -> Path V2 Double -> Path V2 Double Source #

Like union, but takes a tolerance parameter.

difference' :: Double -> FillRule -> Path V2 Double -> Path V2 Double -> Path V2 Double Source #

Like difference, but takes a tolerance parameter.

intersection' :: Double -> FillRule -> Path V2 Double -> Path V2 Double -> Path V2 Double Source #

Like intersection, but takes a tolerance parameter.

exclusion' :: Double -> FillRule -> Path V2 Double -> Path V2 Double -> Path V2 Double Source #

Like exclusion, but takes a tolerance parameter.

Operations on Loops

loopUnion :: Double -> FillRule -> [Located (Trail' Loop V2 Double)] -> [Located (Trail' Loop V2 Double)] Source #

Union of a list of loops.

loopDifference :: Double -> FillRule -> [Located (Trail' Loop V2 Double)] -> [Located (Trail' Loop V2 Double)] -> [Located (Trail' Loop V2 Double)] Source #

Difference between loops. The loops in both lists are first merged using union.

loopIntersection :: Double -> FillRule -> [Located (Trail' Loop V2 Double)] -> [Located (Trail' Loop V2 Double)] -> [Located (Trail' Loop V2 Double)] Source #

Intersection of loops. The loops in both lists are first merged using union.

loopExclusion :: Double -> FillRule -> [Located (Trail' Loop V2 Double)] -> [Located (Trail' Loop V2 Double)] -> [Located (Trail' Loop V2 Double)] Source #

Exclusion (xor) of loops. The loops in both lists are first merged using union.