{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE OverloadedStrings #-}
module Data.Geometry.Ipe.Types(
LayerName(LayerName), layerName
, Image(Image), imageData, rect
, TextLabel(..)
, MiniPage(..), width
, IpeSymbol(Symbol), symbolPoint, symbolName
, Path(Path), pathSegments
, PathSegment(..)
, Group(Group), groupItems
, IpeObject(..), _IpeGroup, _IpeImage, _IpeTextLabel, _IpeMiniPage, _IpeUse, _IpePath
, IpeObject'
, ipeObject'
, ToObject(..)
, IpeAttributes
, Attributes', AttributesOf, AttrMap, AttrMapSym1
, attributes, traverseIpeAttrs
, commonAttributes
, flattenGroups
, View(View), layerNames, activeLayer
, IpeStyle(IpeStyle), styleName, styleData
, basicIpeStyle
, IpePreamble(IpePreamble), encoding, preambleData
, IpeBitmap
, IpePage(IpePage), layers, views, content
, emptyPage, fromContent
, onLayer, contentInView
, withDefaults
, IpeFile(IpeFile), preamble, styles, pages
, ipeFile, singlePageFile, singlePageFromContent
) where
import Control.Lens hiding (views)
import Data.Geometry.Ipe.Attributes hiding (Matrix)
import Data.Geometry.Ipe.Content
import Data.Geometry.Ipe.Layer
import Data.Geometry.Ipe.Literal
import qualified Data.List.NonEmpty as NE
import Data.Maybe (mapMaybe)
import Data.Semigroup (Endo)
import qualified Data.Set as Set
import Data.Text (Text)
import Text.XML.Expat.Tree (Node)
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
emptyPage :: IpePage r
emptyPage = fromContent []
fromContent :: [IpeObject r] -> IpePage r
fromContent obs = IpePage layers' [View layers' a] obs
where
layers' = Set.toList . Set.fromList $ a : mapMaybe (^.commonAttributes.ixAttr SLayer) obs
a = "alpha"
withDefaults :: IpePage r -> IpePage r
withDefaults = addView . addLayer
where
whenNull ys = \case
[] -> ys
xs -> xs
addLayer p = p&layers %~ whenNull ["alpha"]
addView p = p&views %~ whenNull [View (p^.layers) (head $ p^.layers)]
onLayer :: LayerName -> Getting (Endo [IpeObject r]) [IpeObject r] (IpeObject r)
onLayer n = folded.filtered (\o -> o^?commonAttributes._Attr SLayer == Just n)
contentInView :: Word -> Getter (IpePage r) [IpeObject r]
contentInView (fromIntegral -> i) = to inView'
where
inView' p = let lrs = Set.fromList . concatMap (^.layerNames) $ p^..views.ix i
in p^..content.folded.filtered (inVisibleLayer lrs)
inVisibleLayer lrs o = maybe False (`Set.member` lrs) $ o^?commonAttributes._Attr SLayer
data IpeFile r = IpeFile { _preamble :: Maybe IpePreamble
, _styles :: [IpeStyle]
, _pages :: NE.NonEmpty (IpePage r)
}
deriving (Eq,Show)
makeLenses ''IpeFile
ipeFile :: NE.NonEmpty (IpePage r) -> IpeFile r
ipeFile = IpeFile Nothing [basicIpeStyle]
singlePageFile :: IpePage r -> IpeFile r
singlePageFile = ipeFile . (NE.:| [])
singlePageFromContent :: [IpeObject r] -> IpeFile r
singlePageFromContent = singlePageFile . fromContent