-- | 'Path' query functions and related operations. module Graphics.PS.Query (startPt, endPt ,mkValid ,approx, close) where import Data.CG.Minus {- hcg-minus -} import Graphics.PS.Path -- | Locate the starting point of the path, which must begin with a -- 'MoveTo' node. startPt :: Path -> Maybe (Pt Double) startPt path = case path of MoveTo p -> Just p Join p _ -> startPt p _ -> Nothing -- | Variant that allows the initial node to be a 'LineTo' or -- 'CurveTo' node. startPt' :: Path -> Maybe (Pt Double) startPt' path = case path of MoveTo p -> Just p LineTo p -> Just p CurveTo p _ _ -> Just p Join p _ -> startPt' p _ -> Nothing -- | Ensure path begins with a 'MoveTo' node. mkValid :: Path -> Path mkValid path = case startPt' path of Just p -> MoveTo p +++ path Nothing -> path -- | Locate the end point of the path. endPt :: Path -> Maybe (Pt Double) endPt path = case path of MoveTo p -> Just p LineTo p -> Just p CurveTo _ _ p -> Just p Join _ p -> endPt p _ -> Nothing -- | Append a 'LineTo' the start point of 'Path'. close :: Path -> Path close path = case startPt path of Just p -> path +++ ClosePath p Nothing -> path -- | Approximate curves as /n/ straight line segments. That is -- replace 'CurveTo' nodes with /n/ 'LineTo' nodes calculated using -- 'bezier4'. approx :: Double -> Path -> Path approx n path = case path of Join a (CurveTo p2 p3 p4) -> let is = [0, (1.0/n) .. 1.0] l = case endPt a of Just p1 -> map (bezier4 p1 p2 p3 p4) is Nothing -> [] in a +++ line l _ -> path {-- data BBox = BBox Pt Pt deriving (Eq, Show) import Graphics.PS.Transform bboxSum :: BBox -> BBox -> BBox bboxSum (BBox a b) (BBox c d) = BBox (ptMin a c) (ptMax b d) bbox :: Path -> BBox bbox (MoveTo p) = BBox p p bbox (LineTo p) = BBox p p bbox (Join a b) = bbox a `bboxSum` bbox b bbox _ = error "illegal Query" join :: Path -> Path -> Path join a b = a +++ translate x y b where (Pt x y) = endPt a link :: Path -> Path -> Path link a b = a +++ LineTo (startPt b) +++ b relMoveTo :: Path -> Pt -> Path relMoveTo path (Pt dx dy) = path +++ MoveTo (Pt (x + dx) (y + dy)) where (Pt x y) = endPt path relLineTo :: Path -> Pt -> Path relLineTo path (Pt dx dy) = path +++ LineTo (Pt (x + dx) (y + dy)) where (Pt x y) = endPt path hasText :: Path -> Bool hasText (Join p1 p2) = hasText p1 || hasText p2 hasText (Text _ _) = True hasText _ = False --}