{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE OverloadedStrings #-}
module Data.Geometry.Ipe.Types where
import Control.Lens
import Data.Proxy
import Data.Vinyl hiding (Label)
import Data.Ext
import Data.Geometry.Box(Rectangle)
import Data.Geometry.Point
import Data.Geometry.PolyLine
import Data.Geometry.Polygon(SimplePolygon)
import Data.Geometry.Properties
import Data.Geometry.Transformation
import Data.Maybe(mapMaybe)
import Data.Singletons.TH(genDefunSymbols)
import Data.Geometry.Ipe.Literal
import qualified Data.Geometry.Ipe.Attributes as AT
import Data.Geometry.Ipe.Attributes hiding (Matrix)
import Data.Text(Text)
import Text.XML.Expat.Tree(Node)
import GHC.Exts
import qualified Data.List.NonEmpty as NE
import qualified Data.Seq2 as S2
newtype LayerName = LayerName {_layerName :: Text } deriving (Show,Read,Eq,Ord,IsString)
data Image r = Image { _imageData :: ()
, _rect :: Rectangle () r
} deriving (Show,Eq,Ord)
makeLenses ''Image
type instance NumType (Image r) = r
type instance Dimension (Image r) = 2
instance Fractional r => IsTransformable (Image r) where
transformBy t = over rect (transformBy t)
data TextLabel r = Label Text (Point 2 r)
deriving (Show,Eq,Ord)
data MiniPage r = MiniPage Text (Point 2 r) r
deriving (Show,Eq,Ord)
type instance NumType (TextLabel r) = r
type instance Dimension (TextLabel r) = 2
type instance NumType (MiniPage r) = r
type instance Dimension (MiniPage r) = 2
instance Fractional r => IsTransformable (TextLabel r) where
transformBy t (Label txt p) = Label txt (transformBy t p)
instance Fractional r => IsTransformable (MiniPage r) where
transformBy t (MiniPage txt p w) = MiniPage txt (transformBy t p) w
width :: MiniPage t -> t
width (MiniPage _ _ w) = w
data IpeSymbol r = Symbol { _symbolPoint :: Point 2 r
, _symbolName :: Text
}
deriving (Show,Eq,Ord)
makeLenses ''IpeSymbol
type instance NumType (IpeSymbol r) = r
type instance Dimension (IpeSymbol r) = 2
instance Fractional r => IsTransformable (IpeSymbol r) where
transformBy t = over symbolPoint (transformBy t)
data PathSegment r = PolyLineSegment (PolyLine 2 () r)
| PolygonPath (SimplePolygon () r)
| CubicBezierSegment
| QuadraticBezierSegment
| EllipseSegment (Matrix 3 3 r)
| ArcSegment
| SplineSegment
| ClosedSplineSegment
deriving (Show,Eq)
makePrisms ''PathSegment
type instance NumType (PathSegment r) = r
type instance Dimension (PathSegment r) = 2
instance Fractional r => IsTransformable (PathSegment r) where
transformBy t (PolyLineSegment p) = PolyLineSegment $ transformBy t p
transformBy t (PolygonPath p) = PolygonPath $ transformBy t p
transformBy _ _ = error "transformBy: not implemented yet"
newtype Path r = Path { _pathSegments :: S2.ViewL1 (PathSegment r) }
deriving (Show,Eq)
makeLenses ''Path
type instance NumType (Path r) = r
type instance Dimension (Path r) = 2
instance Fractional r => IsTransformable (Path r) where
transformBy t (Path s) = Path $ fmap (transformBy t) s
data Operation r = MoveTo (Point 2 r)
| LineTo (Point 2 r)
| CurveTo (Point 2 r) (Point 2 r) (Point 2 r)
| QCurveTo (Point 2 r) (Point 2 r)
| Ellipse (Matrix 3 3 r)
| ArcTo (Matrix 3 3 r) (Point 2 r)
| Spline [Point 2 r]
| ClosedSpline [Point 2 r]
| ClosePath
deriving (Eq, Show)
makePrisms ''Operation
type family AttrMap (r :: *) (l :: AttributeUniverse) :: * where
AttrMap r 'Layer = LayerName
AttrMap r AT.Matrix = Matrix 3 3 r
AttrMap r Pin = PinType
AttrMap r Transformations = TransformationTypes
AttrMap r Stroke = IpeColor r
AttrMap r Pen = IpePen r
AttrMap r Fill = IpeColor r
AttrMap r Size = IpeSize r
AttrMap r Dash = IpeDash r
AttrMap r LineCap = Int
AttrMap r LineJoin = Int
AttrMap r FillRule = FillType
AttrMap r Arrow = IpeArrow r
AttrMap r RArrow = IpeArrow r
AttrMap r Opacity = IpeOpacity
AttrMap r Tiling = IpeTiling
AttrMap r Gradient = IpeGradient
AttrMap r Clip = Path r
genDefunSymbols [''AttrMap]
newtype Group r = Group { _groupItems :: [IpeObject r] }
deriving (Show,Eq)
type instance NumType (Group r) = r
type instance Dimension (Group r) = 2
instance Fractional r => IsTransformable (Group r) where
transformBy t (Group s) = Group $ fmap (transformBy t) s
type family AttributesOf (t :: * -> *) :: [u] where
AttributesOf Group = GroupAttributes
AttributesOf Image = CommonAttributes
AttributesOf TextLabel = CommonAttributes
AttributesOf MiniPage = CommonAttributes
AttributesOf IpeSymbol = SymbolAttributes
AttributesOf Path = PathAttributes
type Attributes' r = Attributes (AttrMapSym1 r)
type IpeAttributes g r = Attributes' r (AttributesOf g)
type IpeObject' g r = g r :+ IpeAttributes g r
attributes :: Lens' (IpeObject' g r) (IpeAttributes g r)
attributes = extra
data IpeObject r =
IpeGroup (IpeObject' Group r)
| IpeImage (IpeObject' Image r)
| IpeTextLabel (IpeObject' TextLabel r)
| IpeMiniPage (IpeObject' MiniPage r)
| IpeUse (IpeObject' IpeSymbol r)
| IpePath (IpeObject' Path r)
deriving instance (Show r) => Show (IpeObject r)
deriving instance (Eq r) => Eq (IpeObject r)
type instance NumType (IpeObject r) = r
type instance Dimension (IpeObject r) = 2
makePrisms ''IpeObject
makeLenses ''Group
class ToObject i where
ipeObject' :: i r -> IpeAttributes i r -> IpeObject r
instance ToObject Group where ipeObject' g a = IpeGroup (g :+ a)
instance ToObject Image where ipeObject' p a = IpeImage (p :+ a)
instance ToObject TextLabel where ipeObject' p a = IpeTextLabel (p :+ a)
instance ToObject MiniPage where ipeObject' p a = IpeMiniPage (p :+ a)
instance ToObject IpeSymbol where ipeObject' s a = IpeUse (s :+ a)
instance ToObject Path where ipeObject' p a = IpePath (p :+ a)
instance Fractional r => IsTransformable (IpeObject r) where
transformBy t (IpeGroup i) = IpeGroup $ i&core %~ transformBy t
transformBy t (IpeImage i) = IpeImage $ i&core %~ transformBy t
transformBy t (IpeTextLabel i) = IpeTextLabel $ i&core %~ transformBy t
transformBy t (IpeMiniPage i) = IpeMiniPage $ i&core %~ transformBy t
transformBy t (IpeUse i) = IpeUse $ i&core %~ transformBy t
transformBy t (IpePath i) = IpePath $ i&core %~ transformBy t
commonAttributes :: Lens' (IpeObject r) (Attributes (AttrMapSym1 r) CommonAttributes)
commonAttributes = lens (Attrs . g) (\x (Attrs a) -> s x a)
where
select :: (CommonAttributes ⊆ AttributesOf g) =>
Lens' (IpeObject' g r) (Rec (Attr (AttrMapSym1 r)) CommonAttributes)
select = attributes.unAttrs.rsubset
g (IpeGroup i) = i^.select
g (IpeImage i) = i^.select
g (IpeTextLabel i) = i^.select
g (IpeMiniPage i) = i^.select
g (IpeUse i) = i^.select
g (IpePath i) = i^.select
s (IpeGroup i) a = IpeGroup $ i&select .~ a
s (IpeImage i) a = IpeImage $ i&select .~ a
s (IpeTextLabel i) a = IpeTextLabel $ i&select .~ a
s (IpeMiniPage i) a = IpeMiniPage $ i&select .~ a
s (IpeUse i) a = IpeUse $ i&select .~ a
s (IpePath i) a = IpePath $ i&select .~ a
flattenGroups :: [IpeObject r] -> [IpeObject r]
flattenGroups = concatMap flattenGroups'
where
flattenGroups' :: IpeObject r -> [IpeObject r]
flattenGroups' (IpeGroup (Group gs :+ ats)) =
map (applyAts ats) . concatMap flattenGroups' $ gs
where
applyAts _ = id
flattenGroups' o = [o]
data View = View { _layerNames :: [LayerName]
, _activeLayer :: LayerName
}
deriving (Eq, Ord, Show)
makeLenses ''View
data IpeStyle = IpeStyle { _styleName :: Maybe Text
, _styleData :: Node Text Text
}
deriving (Eq,Show)
makeLenses ''IpeStyle
basicIpeStyle :: IpeStyle
basicIpeStyle = IpeStyle (Just "basic") (xmlLiteral [litFile|resources/basic.isy|])
data IpePreamble = IpePreamble { _encoding :: Maybe Text
, _preambleData :: Text
}
deriving (Eq,Read,Show,Ord)
makeLenses ''IpePreamble
type IpeBitmap = Text
data IpePage r = IpePage { _layers :: [LayerName]
, _views :: [View]
, _content :: [IpeObject r]
}
deriving (Eq,Show)
makeLenses ''IpePage
fromContent :: [IpeObject r] -> IpePage r
fromContent obs = IpePage layers' [] obs
where
layers' = mapMaybe (^.commonAttributes.attrLens SLayer) obs
data IpeFile r = IpeFile { _preamble :: Maybe IpePreamble
, _styles :: [IpeStyle]
, _pages :: NE.NonEmpty (IpePage r)
}
deriving (Eq,Show)
makeLenses ''IpeFile
singlePageFile :: IpePage r -> IpeFile r
singlePageFile p = IpeFile Nothing [basicIpeStyle] (p NE.:| [])
singlePageFromContent :: [IpeObject r] -> IpeFile r
singlePageFromContent = singlePageFile . fromContent
applyMatrix' :: ( IsTransformable (i r)
, AT.Matrix ∈ AttributesOf i
, Dimension (i r) ~ 2, r ~ NumType (i r))
=> IpeObject' i r -> IpeObject' i r
applyMatrix' o@(i :+ ats) = maybe o (\m -> transformBy (Transformation m) i :+ ats') mm
where
(mm,ats') = takeAttr (Proxy :: Proxy AT.Matrix) ats
applyMatrix :: Fractional r => IpeObject r -> IpeObject r
applyMatrix (IpeGroup i) = IpeGroup . applyMatrix'
$ i&core.groupItems.traverse %~ applyMatrix
applyMatrix (IpeImage i) = IpeImage $ applyMatrix' i
applyMatrix (IpeTextLabel i) = IpeTextLabel $ applyMatrix' i
applyMatrix (IpeMiniPage i) = IpeMiniPage $ applyMatrix' i
applyMatrix (IpeUse i) = IpeUse $ applyMatrix' i
applyMatrix (IpePath i) = IpePath $ applyMatrix' i
applyMatrices :: Fractional r => IpeFile r -> IpeFile r
applyMatrices f = f&pages.traverse %~ applyMatricesPage
applyMatricesPage :: Fractional r => IpePage r -> IpePage r
applyMatricesPage p = p&content.traverse %~ applyMatrix