module Data.SVG.Tile (TileItem(..), tileSVGs, TileSettings(..)) where
import Control.Applicative ((<$>))
import Control.Arrow ((***), (&&&))
import Control.Monad (liftM)
import Data.Function (on)
import Data.List (groupBy, nub, sortBy)
import Data.Maybe (fromJust, fromMaybe)
import Data.Ord (comparing)
import Data.SVG.SVG
import Data.SVG.Internal.Fail
import Text.XML.Light (unqual, Element(..), Content(..), Attr(..), QName(..))
data TileSettings = TileSettings
{ tilePaperSize :: Size
, tileMargin :: MM
, tileGap :: MM
, ignoreNamespaceConflicts :: Bool
}
deriving (Show, Eq)
data TileItem = TileItem { tileLabel :: String, tileFront :: SVG, tileBack :: Maybe SVG }
sizeAfterMargin :: TileSettings -> Size
sizeAfterMargin (TileSettings (Size pw ph) m _ _)
= Size (pw m m) (ph m m)
data RowInfo = RowInfo {_curX :: MM, _curY :: MM, _rowHeight :: MM }
getTileSize :: DPI -> TileItem -> FailM Size
getTileSize dpi t
= do frontSize <- maybeFail "SVG file has no size" $ getSVGSize dpi (tileFront t)
case tileBack t of
Nothing -> return frontSize
Just back -> do backSize <- maybeFail "SVG file has no size" $ getSVGSize dpi back
return (frontSize `maxSize` backSize)
maxSize :: Size -> Size -> Size
maxSize (Size w h) (Size w' h') = Size (w `max` w') (h `max` h')
type Tiled = ([(QName, String)], [Content])
tileSVGs :: DPI -> TileSettings -> [TileItem] -> Either String [(SVG, Maybe SVG)]
tileSVGs dpi ts toTile = runFail $
do sizes <- mapM (getTileSize dpi) toTile
let make = uncurry $ makeTileSVG dpi ts
tiles <- filter nonBlank <$> tileRow (RowInfo 0 0 0) (zip sizes toTile)
mapM (liftM (make *** fmap make) . doAttrs) tiles
where
merge = mergeAttrs (ignoreNamespaceConflicts ts)
doAttrs :: (Tiled, Maybe Tiled) -> FailM (([Attr], [Content]), Maybe ([Attr], [Content]))
doAttrs (x, Nothing) = flip (,) Nothing <$> merge x
doAttrs (x, Just y) = do x' <- merge x
y' <- merge y
return (x', Just y')
tileRow :: RowInfo -> [(Size, TileItem)] -> FailM [(Tiled, Maybe Tiled)]
tileRow _ [] = return [(([], []), Nothing)]
tileRow ri (svg:svgs)
= case placeAcross ri svg of
Just (ri', el) -> do (es:ess) <- tileRow ri' svgs
return ((el *:* es) : ess)
Nothing -> case placeAcross (RowInfo 0 0 0) svg of
Just (ri', el) ->
do (es:ess) <- tileRow ri' svgs
return ((([], []), Nothing) : (el *:* es) : ess)
Nothing -> Fail $ tileLabel (snd svg) ++ " won't fit on a sheet"
where
(*:*) :: (([a], b), Maybe ([a], b)) -> (([a], [b]), Maybe ([a], [b]))
-> (([a], [b]), Maybe ([a], [b]))
(*:*) (x, my) (xs, mys) = (x & xs, maybe mys (Just . (& fromMaybe ([],[]) mys)) my)
where
(&) (as, b) (as', bs') = (as ++ as', b : bs')
Size pw ph = sizeAfterMargin ts
gap = tileGap ts
nonBlank (xs, mys) = not (nullTile xs) || maybe False (not . nullTile) mys
where
nullTile = null . snd
placeAcross :: RowInfo -> (Size, TileItem) ->
Maybe (RowInfo, (([(QName, String)], Content), Maybe ([(QName, String)], Content)))
placeAcross (RowInfo ox oy rh) (Size w h, t)
| oy + h > ph
= Nothing
| ox + w <= pw
= Just (RowInfo (ox + w + gap) oy (rh `max` h), placeFrontBack t w (ox, oy))
| (oy + rh + gap + h <= ph) && (w <= pw)
= Just (RowInfo (w + gap) (oy + rh + gap) h, placeFrontBack t w (0, oy + rh + gap))
| otherwise = Nothing
placeFrontBack :: TileItem -> MM -> (MM, MM) ->
(([(QName, String)], Content), Maybe ([(QName, String)], Content))
placeFrontBack t w (x, y)
= (namespaces &&& (Elem . placeAt dpi (x, y) . elContent . getSVGElement) $ tileFront t
,(namespaces &&& (Elem . placeAt dpi (flipHoriz w x, y) . elContent . getSVGElement)) <$> tileBack t
)
flipHoriz w x = pw x w
mergeAttrs :: Bool -> ([(QName, String)], a) -> FailM ([Attr], a)
mergeAttrs ignoreConflicts (attrs, x) = flip (,) x <$> mapM fromSingleton merged
where
merged :: [(QName, [String])]
merged = map ((fst . head) &&& (nub . map snd)) $ groupBy ((==) `on` fst) $ sortBy (comparing fst) attrs
fromSingleton :: (QName, [String]) -> FailM Attr
fromSingleton (k, [v]) = return (Attr k v)
fromSingleton (k, vs)
| ignoreConflicts = return (Attr k (head vs))
| otherwise = Fail $ concat
["Conflicting values for namespace "
,maybe "" (++ ":") (qPrefix k)
,qName k
,", values are: "
,show vs
]
makeTileSVG :: DPI -> TileSettings -> [Attr] -> [Content] -> SVG
makeTileSVG dpi (TileSettings (Size pw ph) margin _ _) attrs content
= fromJust . makeSVG $ Element (unqual "svg") (attrs ++
[unqual "version" ~> "1.0"
,unqual "width" ~> show pw
,unqual "height" ~> show ph
])
[Elem $ placeAt dpi (margin, margin) content]
Nothing
where
a ~> b = Attr a b