{-# LANGUAGE UnicodeSyntax #-} {- Module : Graphics.OpenSCAD.Unicode Description : Unicode operators so you can write 'Model' expressions. Copyright : © Mike Meyer, 2014 License : BSD4 Maintainer : mwm@mired.org Stability : experimental -} module Graphics.OpenSCAD.Unicode where import Data.Semigroup ((<>)) import Graphics.OpenSCAD infixl 6 ∪ infixr 6 ∩ infixl 9 ∖ infixl 9 ⊖ infixl 9 ⊕ -- | (∪) = 'union' -- -- U+222A, UNION (∪) :: Vector v => Model v -> Model v -> Model v (∪) = (<>) -- | (∩) = 'intersection' -- -- U+2229, INTERSECTION (∩) :: Vector v => Model v -> Model v -> Model v a ∩ b = intersection [a, b] -- | (∖) = 'difference' -- -- U+2216, SET MINUS (∖):: Vector v => Model v -> Model v -> Model v (∖) = difference -- | (⊖) = Symmetric difference -- -- U+2296, CIRCLED MINUS (⊖) :: Vector v => Model v -> Model v -> Model v a ⊖ b = (a ∖ b) ∪ (b ∖ a) -- | (ࣷ) = 'minkowski' -- -- U+2295, CIRCLED PLUS (⊕) :: Vector v => Model v -> Model v -> Model v a ⊕ b = minkowski [a, b]