{-# LANGUAGE DerivingVia #-}
module Waterfall.Diagram
( Diagram
, LineType (..)
, Visibility (..)
, solidDiagram
, pathDiagram
, diagramLines
, diagramBoundingBox
) where
import Linear.V3 (V3)
import Linear.V2 (V2)
import Linear (_xy)
import Control.Lens ((^.))
import Waterfall.Internal.Solid (Solid (), acquireSolid)
import qualified OpenCascade.HLRBRep.TypeOfResultingEdge as HLRBRep
import qualified OpenCascade.HLRBRep.Algo as HLRBRep.Algo
import qualified OpenCascade.HLRAlgo.Projector as HLRAlgo.Projector
import qualified OpenCascade.HLRBRep.HLRToShape as HLRBRep.HLRToShape
import qualified OpenCascade.GP as GP
import qualified OpenCascade.GP.Ax2 as GP.Ax2
import qualified OpenCascade.Bnd.Box as Bnd.Box
import qualified OpenCascade.BRepBndLib as BRepBndLib
import Waterfall.Internal.ToOpenCascade (v3ToDir)
import Waterfall.TwoD.Internal.Path2D (Path2D (..))
import Control.Monad.IO.Class (liftIO)
import Waterfall.Internal.Finalizers (unsafeFromAcquire, unsafeFromAcquireT)
import Waterfall.Internal.Edges (allEdges, buildEdgeCurve3D, edgeToWire)
import Waterfall.Internal.Path.Common (RawPath (..))
import Waterfall.Internal.Diagram (RawDiagram (..))
import Waterfall.TwoD.Transforms (Transformable2D)
import Waterfall.Internal.FromOpenCascade (gpPntToV3)
import OpenCascade.Inheritance (upcast)
import Control.Monad (forM_)
newtype Diagram = Diagram { Diagram -> RawDiagram
rawDiagram :: RawDiagram }
deriving (NonEmpty Diagram -> Diagram
Diagram -> Diagram -> Diagram
(Diagram -> Diagram -> Diagram)
-> (NonEmpty Diagram -> Diagram)
-> (forall b. Integral b => b -> Diagram -> Diagram)
-> Semigroup Diagram
forall b. Integral b => b -> Diagram -> Diagram
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: Diagram -> Diagram -> Diagram
<> :: Diagram -> Diagram -> Diagram
$csconcat :: NonEmpty Diagram -> Diagram
sconcat :: NonEmpty Diagram -> Diagram
$cstimes :: forall b. Integral b => b -> Diagram -> Diagram
stimes :: forall b. Integral b => b -> Diagram -> Diagram
Semigroup, Semigroup Diagram
Diagram
Semigroup Diagram =>
Diagram
-> (Diagram -> Diagram -> Diagram)
-> ([Diagram] -> Diagram)
-> Monoid Diagram
[Diagram] -> Diagram
Diagram -> Diagram -> Diagram
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
$cmempty :: Diagram
mempty :: Diagram
$cmappend :: Diagram -> Diagram -> Diagram
mappend :: Diagram -> Diagram -> Diagram
$cmconcat :: [Diagram] -> Diagram
mconcat :: [Diagram] -> Diagram
Monoid, Double -> Diagram -> Diagram
V2 Double -> Diagram -> Diagram
M23 Double -> Diagram -> Diagram
(M23 Double -> Diagram -> Diagram)
-> (Double -> Diagram -> Diagram)
-> (V2 Double -> Diagram -> Diagram)
-> (Double -> Diagram -> Diagram)
-> (V2 Double -> Diagram -> Diagram)
-> (V2 Double -> Diagram -> Diagram)
-> Transformable2D Diagram
forall a.
(M23 Double -> a -> a)
-> (Double -> a -> a)
-> (V2 Double -> a -> a)
-> (Double -> a -> a)
-> (V2 Double -> a -> a)
-> (V2 Double -> a -> a)
-> Transformable2D a
$cmatTransform2D :: M23 Double -> Diagram -> Diagram
matTransform2D :: M23 Double -> Diagram -> Diagram
$crotate2D :: Double -> Diagram -> Diagram
rotate2D :: Double -> Diagram -> Diagram
$cscale2D :: V2 Double -> Diagram -> Diagram
scale2D :: V2 Double -> Diagram -> Diagram
$cuScale2D :: Double -> Diagram -> Diagram
uScale2D :: Double -> Diagram -> Diagram
$ctranslate2D :: V2 Double -> Diagram -> Diagram
translate2D :: V2 Double -> Diagram -> Diagram
$cmirror2D :: V2 Double -> Diagram -> Diagram
mirror2D :: V2 Double -> Diagram -> Diagram
Transformable2D) via RawDiagram
data LineType =
OutLine
| SharpLine
| RawLine HLRBRep.TypeOfResultingEdge
deriving (LineType -> LineType -> Bool
(LineType -> LineType -> Bool)
-> (LineType -> LineType -> Bool) -> Eq LineType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LineType -> LineType -> Bool
== :: LineType -> LineType -> Bool
$c/= :: LineType -> LineType -> Bool
/= :: LineType -> LineType -> Bool
Eq, Eq LineType
Eq LineType =>
(LineType -> LineType -> Ordering)
-> (LineType -> LineType -> Bool)
-> (LineType -> LineType -> Bool)
-> (LineType -> LineType -> Bool)
-> (LineType -> LineType -> Bool)
-> (LineType -> LineType -> LineType)
-> (LineType -> LineType -> LineType)
-> Ord LineType
LineType -> LineType -> Bool
LineType -> LineType -> Ordering
LineType -> LineType -> LineType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: LineType -> LineType -> Ordering
compare :: LineType -> LineType -> Ordering
$c< :: LineType -> LineType -> Bool
< :: LineType -> LineType -> Bool
$c<= :: LineType -> LineType -> Bool
<= :: LineType -> LineType -> Bool
$c> :: LineType -> LineType -> Bool
> :: LineType -> LineType -> Bool
$c>= :: LineType -> LineType -> Bool
>= :: LineType -> LineType -> Bool
$cmax :: LineType -> LineType -> LineType
max :: LineType -> LineType -> LineType
$cmin :: LineType -> LineType -> LineType
min :: LineType -> LineType -> LineType
Ord, Int -> LineType -> ShowS
[LineType] -> ShowS
LineType -> String
(Int -> LineType -> ShowS)
-> (LineType -> String) -> ([LineType] -> ShowS) -> Show LineType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LineType -> ShowS
showsPrec :: Int -> LineType -> ShowS
$cshow :: LineType -> String
show :: LineType -> String
$cshowList :: [LineType] -> ShowS
showList :: [LineType] -> ShowS
Show)
lineTypeToOpenCascade :: LineType -> HLRBRep.TypeOfResultingEdge
lineTypeToOpenCascade :: LineType -> TypeOfResultingEdge
lineTypeToOpenCascade LineType
OutLine = TypeOfResultingEdge
HLRBRep.OutLine
lineTypeToOpenCascade LineType
SharpLine = TypeOfResultingEdge
HLRBRep.Sharp
lineTypeToOpenCascade (RawLine TypeOfResultingEdge
lt) = TypeOfResultingEdge
lt
data Visibility = Visible | Hidden deriving (Visibility -> Visibility -> Bool
(Visibility -> Visibility -> Bool)
-> (Visibility -> Visibility -> Bool) -> Eq Visibility
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Visibility -> Visibility -> Bool
== :: Visibility -> Visibility -> Bool
$c/= :: Visibility -> Visibility -> Bool
/= :: Visibility -> Visibility -> Bool
Eq, Eq Visibility
Eq Visibility =>
(Visibility -> Visibility -> Ordering)
-> (Visibility -> Visibility -> Bool)
-> (Visibility -> Visibility -> Bool)
-> (Visibility -> Visibility -> Bool)
-> (Visibility -> Visibility -> Bool)
-> (Visibility -> Visibility -> Visibility)
-> (Visibility -> Visibility -> Visibility)
-> Ord Visibility
Visibility -> Visibility -> Bool
Visibility -> Visibility -> Ordering
Visibility -> Visibility -> Visibility
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Visibility -> Visibility -> Ordering
compare :: Visibility -> Visibility -> Ordering
$c< :: Visibility -> Visibility -> Bool
< :: Visibility -> Visibility -> Bool
$c<= :: Visibility -> Visibility -> Bool
<= :: Visibility -> Visibility -> Bool
$c> :: Visibility -> Visibility -> Bool
> :: Visibility -> Visibility -> Bool
$c>= :: Visibility -> Visibility -> Bool
>= :: Visibility -> Visibility -> Bool
$cmax :: Visibility -> Visibility -> Visibility
max :: Visibility -> Visibility -> Visibility
$cmin :: Visibility -> Visibility -> Visibility
min :: Visibility -> Visibility -> Visibility
Ord, Int -> Visibility -> ShowS
[Visibility] -> ShowS
Visibility -> String
(Int -> Visibility -> ShowS)
-> (Visibility -> String)
-> ([Visibility] -> ShowS)
-> Show Visibility
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Visibility -> ShowS
showsPrec :: Int -> Visibility -> ShowS
$cshow :: Visibility -> String
show :: Visibility -> String
$cshowList :: [Visibility] -> ShowS
showList :: [Visibility] -> ShowS
Show)
solidDiagram :: V3 Double -> Solid -> Diagram
solidDiagram :: V3 Double -> Solid -> Diagram
solidDiagram V3 Double
projectionDirection Solid
solid = RawDiagram -> Diagram
Diagram (RawDiagram -> Diagram)
-> (Acquire
(TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge])
-> RawDiagram)
-> Acquire
(TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge])
-> Diagram
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge])
-> RawDiagram
RawDiagram ((TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge])
-> RawDiagram)
-> (Acquire
(TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge])
-> TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge])
-> Acquire
(TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge])
-> RawDiagram
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Acquire (TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge])
-> TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge]
forall a. Acquire a -> a
unsafeFromAcquire (Acquire
(TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge])
-> Diagram)
-> Acquire
(TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge])
-> Diagram
forall a b. (a -> b) -> a -> b
$ do
Ptr Shape
s' <- Solid -> Acquire (Ptr Shape)
acquireSolid Solid
solid
Ptr (Handle Algo)
algo <- Acquire (Ptr (Handle Algo))
HLRBRep.Algo.new
IO () -> Acquire ()
forall a. IO a -> Acquire a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Acquire ()) -> IO () -> Acquire ()
forall a b. (a -> b) -> a -> b
$ Ptr (Handle Algo) -> Ptr Shape -> IO ()
HLRBRep.Algo.add Ptr (Handle Algo)
algo Ptr Shape
s'
Ptr Pnt
o <- Acquire (Ptr Pnt)
GP.origin
Ptr Dir
d <- V3 Double -> Acquire (Ptr Dir)
v3ToDir V3 Double
projectionDirection
Ptr Projector
projector <- Ptr Ax2 -> Acquire (Ptr Projector)
HLRAlgo.Projector.fromAx2 (Ptr Ax2 -> Acquire (Ptr Projector))
-> Acquire (Ptr Ax2) -> Acquire (Ptr Projector)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr Pnt -> Ptr Dir -> Acquire (Ptr Ax2)
GP.Ax2.newAutoX Ptr Pnt
o Ptr Dir
d
IO () -> Acquire ()
forall a. IO a -> Acquire a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Acquire ()) -> IO () -> Acquire ()
forall a b. (a -> b) -> a -> b
$ do
Ptr (Handle Algo) -> Ptr Projector -> IO ()
HLRBRep.Algo.projector Ptr (Handle Algo)
algo Ptr Projector
projector
Ptr (Handle Algo) -> IO ()
HLRBRep.Algo.update Ptr (Handle Algo)
algo
Ptr (Handle Algo) -> IO ()
HLRBRep.Algo.hide Ptr (Handle Algo)
algo
Ptr HLRToShape
extractor <- Ptr (Handle Algo) -> Acquire (Ptr HLRToShape)
HLRBRep.HLRToShape.fromAlgo Ptr (Handle Algo)
algo
(TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge])
-> Acquire
(TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge])
forall a. a -> Acquire a
forall (m :: * -> *) a. Monad m => a -> m a
return ((TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge])
-> Acquire
(TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge]))
-> (TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge])
-> Acquire
(TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge])
forall a b. (a -> b) -> a -> b
$ \TypeOfResultingEdge
lt Bool
v Bool
is3D -> do
Ptr Shape
compoundOfEdges <- Ptr HLRToShape
-> TypeOfResultingEdge -> Bool -> Bool -> Acquire (Ptr Shape)
HLRBRep.HLRToShape.compoundOfEdges Ptr HLRToShape
extractor TypeOfResultingEdge
lt Bool
v Bool
is3D
[Ptr Edge]
rawEdges <- Ptr Shape -> Acquire [Ptr Edge]
allEdges Ptr Shape
compoundOfEdges
(Ptr Edge -> Acquire (Ptr Edge))
-> [Ptr Edge] -> Acquire [Ptr Edge]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Ptr Edge -> Acquire (Ptr Edge)
buildEdgeCurve3D [Ptr Edge]
rawEdges
pathDiagram :: LineType -> Visibility -> Path2D -> Diagram
pathDiagram :: LineType -> Visibility -> Path2D -> Diagram
pathDiagram LineType
lt Visibility
v (Path2D RawPath
rawpath) =
RawDiagram -> Diagram
Diagram (RawDiagram -> Diagram)
-> ((TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge])
-> RawDiagram)
-> (TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge])
-> Diagram
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge])
-> RawDiagram
RawDiagram ((TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge])
-> Diagram)
-> (TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge])
-> Diagram
forall a b. (a -> b) -> a -> b
$ \TypeOfResultingEdge
lt' Bool
v' Bool
_ ->
if LineType -> TypeOfResultingEdge
lineTypeToOpenCascade LineType
lt TypeOfResultingEdge -> TypeOfResultingEdge -> Bool
forall a. Eq a => a -> a -> Bool
== TypeOfResultingEdge
lt' Bool -> Bool -> Bool
&& (Visibility
v Visibility -> Visibility -> Bool
forall a. Eq a => a -> a -> Bool
== Visibility
Visible) Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Bool
v'
then case RawPath
rawpath of
(ComplexRawPath Ptr Wire
wire) -> Ptr Shape -> Acquire [Ptr Edge]
allEdges (Ptr Wire -> Ptr Shape
forall a b. SubTypeOf a b => Ptr b -> Ptr a
upcast Ptr Wire
wire)
RawPath
_ -> [Ptr Edge] -> Acquire [Ptr Edge]
forall a. a -> Acquire a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
else [Ptr Edge] -> Acquire [Ptr Edge]
forall a. a -> Acquire a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
diagramLines :: LineType -> Visibility -> Diagram -> [Path2D]
diagramLines :: LineType -> Visibility -> Diagram -> [Path2D]
diagramLines LineType
lt Visibility
v Diagram
d = Acquire [Path2D] -> [Path2D]
forall (t :: * -> *) a. Traversable t => Acquire (t a) -> t a
unsafeFromAcquireT (Acquire [Path2D] -> [Path2D]) -> Acquire [Path2D] -> [Path2D]
forall a b. (a -> b) -> a -> b
$ do
[Ptr Edge]
edges <- RawDiagram
-> TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge]
runDiagram (Diagram -> RawDiagram
rawDiagram Diagram
d) (LineType -> TypeOfResultingEdge
lineTypeToOpenCascade LineType
lt) (Visibility
v Visibility -> Visibility -> Bool
forall a. Eq a => a -> a -> Bool
== Visibility
Visible) Bool
False
[Ptr Wire]
wires <- (Ptr Edge -> Acquire (Ptr Wire))
-> [Ptr Edge] -> Acquire [Ptr Wire]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Ptr Edge -> Acquire (Ptr Wire)
edgeToWire [Ptr Edge]
edges
[Path2D] -> Acquire [Path2D]
forall a. a -> Acquire a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Path2D] -> Acquire [Path2D]) -> [Path2D] -> Acquire [Path2D]
forall a b. (a -> b) -> a -> b
$ (RawPath -> Path2D
Path2D (RawPath -> Path2D) -> (Ptr Wire -> RawPath) -> Ptr Wire -> Path2D
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Wire -> RawPath
ComplexRawPath) (Ptr Wire -> Path2D) -> [Ptr Wire] -> [Path2D]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Ptr Wire]
wires
diagramBoundingBox :: Diagram -> Maybe (V2 Double, V2 Double)
diagramBoundingBox :: Diagram -> Maybe (V2 Double, V2 Double)
diagramBoundingBox Diagram
d = Acquire (Maybe (V2 Double, V2 Double))
-> Maybe (V2 Double, V2 Double)
forall a. Acquire a -> a
unsafeFromAcquire (Acquire (Maybe (V2 Double, V2 Double))
-> Maybe (V2 Double, V2 Double))
-> Acquire (Maybe (V2 Double, V2 Double))
-> Maybe (V2 Double, V2 Double)
forall a b. (a -> b) -> a -> b
$ do
[Ptr Edge]
outline <- RawDiagram
-> TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge]
runDiagram (Diagram -> RawDiagram
rawDiagram Diagram
d) TypeOfResultingEdge
HLRBRep.OutLine Bool
True Bool
False
[Ptr Edge]
sharpLine <- RawDiagram
-> TypeOfResultingEdge -> Bool -> Bool -> Acquire [Ptr Edge]
runDiagram (Diagram -> RawDiagram
rawDiagram Diagram
d) TypeOfResultingEdge
HLRBRep.Sharp Bool
True Bool
False
let allLines :: [Ptr Edge]
allLines = [Ptr Edge]
outline [Ptr Edge] -> [Ptr Edge] -> [Ptr Edge]
forall a. Semigroup a => a -> a -> a
<> [Ptr Edge]
sharpLine
if [Ptr Edge] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Ptr Edge]
allLines
then Maybe (V2 Double, V2 Double)
-> Acquire (Maybe (V2 Double, V2 Double))
forall a. a -> Acquire a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (V2 Double, V2 Double)
forall a. Maybe a
Nothing
else do
Ptr Box
theBox <- Acquire (Ptr Box)
Bnd.Box.new
[Ptr Edge] -> (Ptr Edge -> Acquire ()) -> Acquire ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Ptr Edge]
allLines ((Ptr Edge -> Acquire ()) -> Acquire ())
-> (Ptr Edge -> Acquire ()) -> Acquire ()
forall a b. (a -> b) -> a -> b
$ \Ptr Edge
s -> (IO () -> Acquire ()
forall a. IO a -> Acquire a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Acquire ()) -> IO () -> Acquire ()
forall a b. (a -> b) -> a -> b
$ Ptr Shape -> Ptr Box -> Bool -> Bool -> IO ()
BRepBndLib.addOptimal (Ptr Edge -> Ptr Shape
forall a b. SubTypeOf a b => Ptr b -> Ptr a
upcast Ptr Edge
s) Ptr Box
theBox Bool
True Bool
False)
V3 Double
p1 <- IO (V3 Double) -> Acquire (V3 Double)
forall a. IO a -> Acquire a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (V3 Double) -> Acquire (V3 Double))
-> (Ptr Pnt -> IO (V3 Double)) -> Ptr Pnt -> Acquire (V3 Double)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Pnt -> IO (V3 Double)
gpPntToV3 (Ptr Pnt -> Acquire (V3 Double))
-> Acquire (Ptr Pnt) -> Acquire (V3 Double)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr Box -> Acquire (Ptr Pnt)
Bnd.Box.cornerMin Ptr Box
theBox
V3 Double
p2 <- IO (V3 Double) -> Acquire (V3 Double)
forall a. IO a -> Acquire a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (V3 Double) -> Acquire (V3 Double))
-> (Ptr Pnt -> IO (V3 Double)) -> Ptr Pnt -> Acquire (V3 Double)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Pnt -> IO (V3 Double)
gpPntToV3 (Ptr Pnt -> Acquire (V3 Double))
-> Acquire (Ptr Pnt) -> Acquire (V3 Double)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr Box -> Acquire (Ptr Pnt)
Bnd.Box.cornerMax Ptr Box
theBox
Maybe (V2 Double, V2 Double)
-> Acquire (Maybe (V2 Double, V2 Double))
forall a. a -> Acquire a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe (V2 Double, V2 Double)
-> Acquire (Maybe (V2 Double, V2 Double)))
-> Maybe (V2 Double, V2 Double)
-> Acquire (Maybe (V2 Double, V2 Double))
forall a b. (a -> b) -> a -> b
$ (V2 Double, V2 Double) -> Maybe (V2 Double, V2 Double)
forall a. a -> Maybe a
Just (V3 Double
p1 V3 Double
-> Getting (V2 Double) (V3 Double) (V2 Double) -> V2 Double
forall s a. s -> Getting a s a -> a
^. Getting (V2 Double) (V3 Double) (V2 Double)
forall a. Lens' (V3 a) (V2 a)
forall (t :: * -> *) a. R2 t => Lens' (t a) (V2 a)
_xy, V3 Double
p2 V3 Double
-> Getting (V2 Double) (V3 Double) (V2 Double) -> V2 Double
forall s a. s -> Getting a s a -> a
^. Getting (V2 Double) (V3 Double) (V2 Double)
forall a. Lens' (V3 a) (V2 a)
forall (t :: * -> *) a. R2 t => Lens' (t a) (V2 a)
_xy)