module Data.Geometry.Ipe.FromIpe where
import Control.Applicative
import qualified Data.Traversable as Tr
import Data.Ext
import Data.Geometry.Ipe.Types
import Data.Geometry.Line
import Data.Geometry.LineSegment
import qualified Data.Geometry.PolyLine as PolyLine
import Data.Geometry.Polygon
import Control.Lens
import qualified Data.Seq2 as S2
_asLineSegment :: Prism' (Path r) (LineSegment 2 () r)
_asLineSegment = prism' seg2path path2seg
where
seg2path = review _asPolyLine . PolyLine.fromLineSegment
path2seg p = PolyLine.asLineSegment' =<< preview _asPolyLine p
_asPolyLine :: Prism' (Path r) (PolyLine.PolyLine 2 () r)
_asPolyLine = prism' poly2path path2poly
where
poly2path = Path . S2.l1Singleton . PolyLineSegment
path2poly = preview (pathSegments.Tr.traverse._PolyLineSegment)
_asSimplePolygon :: Prism' (Path r) (SimplePolygon () r)
_asSimplePolygon = prism' poly2path path2poly
where
poly2path = Path . S2.l1Singleton . PolygonPath
path2poly = preview (pathSegments.Tr.traverse._PolygonPath)
_withAttrs :: Prism' (IpeObject r) (i r :+ IpeAttributes i r) -> Prism' (i r) g
-> Prism' (IpeObject r) (g :+ IpeAttributes i r)
_withAttrs po pg = prism' g2o o2g
where
g2o = review po . over core (review pg)
o2g o = preview po o >>= \(i :+ ats) -> (:+ ats) <$> preview pg i