module Data.Geometry.Ipe.IpeOut where
import Control.Lens
import Data.Bifunctor
import Data.Ext
import Data.Geometry.Ball
import Data.Geometry.Boundary
import Data.Geometry.Box
import Data.Geometry.Ipe.Attributes
import Data.Geometry.Ipe.Types
import Data.Geometry.LineSegment
import Data.Geometry.Point
import Data.Geometry.PolyLine
import Data.Geometry.Polygon
import Data.Geometry.Polygon.Convex
import Data.Geometry.Properties
import Data.Geometry.Transformation
import Data.Semigroup
import qualified Data.Seq2 as S2
import Data.Text (Text)
newtype IpeOut g i = IpeOut { asIpe :: g -> i } deriving (Functor)
asIpeObject :: (HasDefaultIpeOut g, DefaultIpeOut g ~ i, NumType g ~ r)
=> g -> IpeAttributes i r -> IpeObject r
asIpeObject = asIpeObjectWith defaultIpeOut
asIpeObject' :: (HasDefaultIpeOut g, DefaultIpeOut g ~ i, NumType g ~ r)
=> IpeAttributes i r -> g -> IpeObject r
asIpeObject' = flip asIpeObject
asIpeObjectWith :: (ToObject i, NumType g ~ r)
=> IpeOut g (IpeObject' i r) -> g -> IpeAttributes i r -> IpeObject r
asIpeObjectWith io g ats = asIpe (ipeObject io ats) g
asIpeGroup :: [IpeObject r] -> IpeObject r
asIpeGroup = flip asIpeGroup' mempty
asIpeGroup' :: [IpeObject r] -> IpeAttributes Group r -> IpeObject r
asIpeGroup' gs ats = IpeGroup $ Group gs :+ ats
ipeObject :: (ToObject i, NumType g ~ r)
=> IpeOut g (IpeObject' i r) -> IpeAttributes i r -> IpeOut g (IpeObject r)
ipeObject io ats = IpeOut $ \g -> let (i :+ ats') = asIpe io g
in ipeObject' i (ats' <> ats)
coreOut :: IpeOut g i -> IpeOut (g :+ a) i
coreOut io = IpeOut $ asIpe io . (^.core)
class ToObject (DefaultIpeOut g) => HasDefaultIpeOut g where
type DefaultIpeOut g :: * -> *
defaultIpeOut :: IpeOut g (IpeObject' (DefaultIpeOut g) (NumType g))
instance HasDefaultIpeOut (Point 2 r) where
type DefaultIpeOut (Point 2 r) = IpeSymbol
defaultIpeOut = ipeDiskMark
instance HasDefaultIpeOut (LineSegment 2 p r) where
type DefaultIpeOut (LineSegment 2 p r) = Path
defaultIpeOut = ipeLineSegment
instance Floating r => HasDefaultIpeOut (Disk p r) where
type DefaultIpeOut (Disk p r) = Path
defaultIpeOut = ipeDisk
instance HasDefaultIpeOut (PolyLine 2 p r) where
type DefaultIpeOut (PolyLine 2 p r) = Path
defaultIpeOut = noAttrs ipePolyLine
instance HasDefaultIpeOut (SimplePolygon p r) where
type DefaultIpeOut (SimplePolygon p r) = Path
defaultIpeOut = flip addAttributes ipeSimplePolygon $
mempty <> attr SFill (IpeColor "red")
instance HasDefaultIpeOut (ConvexPolygon p r) where
type DefaultIpeOut (ConvexPolygon p r) = Path
defaultIpeOut = IpeOut $ asIpe defaultIpeOut . view simplePolygon
ipeMark :: Text -> IpeOut (Point 2 r) (IpeObject' IpeSymbol r)
ipeMark n = noAttrs . IpeOut $ flip Symbol n
ipeDiskMark :: IpeOut (Point 2 r) (IpeObject' IpeSymbol r)
ipeDiskMark = ipeMark "mark/disk(sx)"
noAttrs :: Monoid extra => IpeOut g core -> IpeOut g (core :+ extra)
noAttrs = addAttributes mempty
addAttributes :: extra -> IpeOut g core -> IpeOut g (core :+ extra)
addAttributes ats io = IpeOut $ \g -> asIpe io g :+ ats
defaultClipRectangle :: (Num r, Ord r) => Rectangle () r
defaultClipRectangle = boundingBox (point2 (200) (200)) <>
boundingBox (point2 1000 1000)
ipeLineSegment :: IpeOut (LineSegment 2 p r) (IpeObject' Path r)
ipeLineSegment = noAttrs $ fromPathSegment ipeLineSegment'
ipeLineSegment' :: IpeOut (LineSegment 2 p r) (PathSegment r)
ipeLineSegment' = IpeOut $ PolyLineSegment . fromLineSegment . first (const ())
ipePolyLine :: IpeOut (PolyLine 2 p r) (Path r)
ipePolyLine = fromPathSegment ipePolyLine'
ipePolyLine' :: IpeOut (PolyLine 2 a r) (PathSegment r)
ipePolyLine' = IpeOut $ PolyLineSegment . first (const ())
ipeDisk :: Floating r => IpeOut (Disk p r) (IpeObject' Path r)
ipeDisk = noAttrs . IpeOut $ asIpe ipeCircle . Boundary
ipeCircle :: Floating r => IpeOut (Circle p r) (Path r)
ipeCircle = fromPathSegment ipeCircle'
ipeCircle' :: Floating r => IpeOut (Circle p r) (PathSegment r)
ipeCircle' = IpeOut circle''
where
circle'' (Circle (c :+ _) r) = EllipseSegment m
where
m = translation (toVec c) |.| uniformScaling (sqrt r) ^. transformationMatrix
fromPathSegment :: IpeOut g (PathSegment r) -> IpeOut g (Path r)
fromPathSegment io = IpeOut $ Path . S2.l1Singleton . asIpe io
ipeSimplePolygon :: IpeOut (SimplePolygon p r) (Path r)
ipeSimplePolygon = fromPathSegment . IpeOut $ PolygonPath . dropExt
where
dropExt :: SimplePolygon p r -> SimplePolygon () r
dropExt (SimplePolygon vs) = SimplePolygon $ fmap (&extra .~ ()) vs