module Types where import Text.XML.Light.Types import Data.List (groupBy) import Debug.Trace (trace) import Color import Helpers (replace, clean) import TextElement import Point import PathCommand import Data.List (find) import Data.Maybe (fromJust) type Id = String -- returns Just ID or Nothing, if supplied string is empty getId :: Maybe String -> Maybe Id getId s = s -- key value pair - maybe Map would do the trick? data KeyValuePair = KeyValuePair { key :: String , value :: String} deriving (Show, Eq) getStringFromKVP :: String -> [KeyValuePair] -> Maybe String getStringFromKVP s kvp = let sr = find (\x -> key x == s) kvp in if sr == Nothing then Nothing else Just $ value (fromJust sr) -- key elements data GraphicsElement = Rect { coordinate :: Point , width :: Float , height :: Float , rx :: Float , ry :: Float , fill :: Maybe Color , strokeWidth :: Float , stroke :: Maybe Color , id :: Maybe Id } | Circle { coordinate :: Point , radius :: Float , fill :: Maybe Color , strokeWidth :: Float , stroke :: Maybe Color , id :: Maybe Id } | Ellipse { coordinate :: Point , rx :: Float , ry :: Float , fill :: Maybe Color , strokeWidth :: Float , stroke :: Maybe Color , id :: Maybe Id } | Line { coordinateStart :: Point , coordinateStop :: Point , strokeWidth :: Float , stroke :: Maybe Color , id :: Maybe Id } | Group { gElements :: [GraphicsElement] , gId :: Maybe Id } | Description | Definition | Path { commands :: [PathCommand] , id :: Maybe Id , fill :: Maybe Color , strokeWidth :: Float , stroke :: Maybe Color } | TextElement { text :: TextElement , id :: Maybe Id } | NothingYet | SomethingNotSimple deriving (Show, Eq) mkPolyline :: [Point] -> Maybe Color -> Float -> Maybe Color -> Maybe Id -> GraphicsElement mkPolyline (fp:ps) fill strokewidth stroke id = Path (PathMoveTo fp:map PathLineTo ps) id fill strokewidth stroke