{-# LANGUAGE OverloadedStrings #-}
module Data.Geometry.Ipe.FromIpe where
import Control.Lens hiding (Simple)
import Data.Ext
import Data.Geometry.Ipe.Reader
import Data.Geometry.Ipe.Types
import Data.Geometry.LineSegment
import qualified Data.Geometry.PolyLine as PolyLine
import Data.Geometry.Polygon
import Data.Geometry.Properties
import Data.Geometry.Triangle
import qualified Data.LSeq as LSeq
import Data.List.NonEmpty (NonEmpty(..))
_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 . fromSingleton . PolyLineSegment
path2poly = preview (pathSegments.traverse._PolyLineSegment)
_asSimplePolygon :: Prism' (Path r) (Polygon Simple () r)
_asSimplePolygon = _asSomePolygon._Left
_asTriangle :: Prism' (Path r) (Triangle 2 () r)
_asTriangle = prism' triToPath path2tri
where
triToPath (Triangle p q r) = polygonToPath . fromPoints . map (&extra .~ ()) $ [p,q,r]
path2tri p = case p^..pathSegments.traverse._PolygonPath of
[] -> Nothing
[pg] -> case polygonVertices pg of
(a :| [b,c]) -> Just $ Triangle a b c
_ -> Nothing
_ -> Nothing
_asMultiPolygon :: Prism' (Path r) (MultiPolygon () r)
_asMultiPolygon = _asSomePolygon._Right
_asSomePolygon :: Prism' (Path r) (SomePolygon () r)
_asSomePolygon = prism' embed pathToPolygon
where
embed = either polygonToPath polygonToPath
polygonToPath :: Polygon t () r -> Path r
polygonToPath pg@(SimplePolygon _) = Path . fromSingleton . PolygonPath $ pg
polygonToPath (MultiPolygon vs hs) = Path . LSeq.fromNonEmpty . fmap PolygonPath
$ (SimplePolygon vs) :| hs
pathToPolygon :: Path r -> Maybe (Either (SimplePolygon () r) (MultiPolygon () r))
pathToPolygon p = case p^..pathSegments.traverse._PolygonPath of
[] -> Nothing
[pg] -> Just . Left $ pg
SimplePolygon vs: hs -> Just . Right $ MultiPolygon vs hs
_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
class HasDefaultFromIpe g where
type DefaultFromIpe g :: * -> *
defaultFromIpe :: (r ~ NumType g)
=> Prism' (IpeObject r) (g :+ IpeAttributes (DefaultFromIpe g) r)
instance HasDefaultFromIpe (LineSegment 2 () r) where
type DefaultFromIpe (LineSegment 2 () r) = Path
defaultFromIpe = _withAttrs _IpePath _asLineSegment
instance HasDefaultFromIpe (PolyLine.PolyLine 2 () r) where
type DefaultFromIpe (PolyLine.PolyLine 2 () r) = Path
defaultFromIpe = _withAttrs _IpePath _asPolyLine
instance HasDefaultFromIpe (SimplePolygon () r) where
type DefaultFromIpe (SimplePolygon () r) = Path
defaultFromIpe = _withAttrs _IpePath _asSimplePolygon
instance HasDefaultFromIpe (MultiPolygon () r) where
type DefaultFromIpe (MultiPolygon () r) = Path
defaultFromIpe = _withAttrs _IpePath _asMultiPolygon
readAll :: (HasDefaultFromIpe g, r ~ NumType g, Foldable f)
=> f (IpePage r) -> [g :+ IpeAttributes (DefaultFromIpe g) r]
readAll = foldMap (^..content.traverse.defaultFromIpe)
readAllFrom :: (HasDefaultFromIpe g, r ~ NumType g, Coordinate r, Eq r)
=> FilePath -> IO [g :+ IpeAttributes (DefaultFromIpe g) r]
readAllFrom fp = readAll <$> readSinglePageFile fp
fromSingleton :: a -> LSeq.LSeq 1 a
fromSingleton = LSeq.fromNonEmpty . (:| [])