{-# LANGUAGE DeriveGeneric, DeriveAnyClass #-}
module Eventloop.Module.BasicShapes.Types
( module Eventloop.Module.BasicShapes.Types
, CanvasId
, Alignment(..)
) where
import Eventloop.Module.Websocket.Canvas.Types (CanvasId, Alignment(..))
import Eventloop.Utility.Vectors
import GHC.Generics (Generic)
import Control.DeepSeq
type GraphicalNumeric = Float
type Position = Point
type Width = GraphicalNumeric
type Height = GraphicalNumeric
type Dimensions = (Width, Height)
type Radius = GraphicalNumeric
type Red = GraphicalNumeric
type Green = GraphicalNumeric
type Blue = GraphicalNumeric
type Alpha = GraphicalNumeric
type Color = (Red, Green, Blue, Alpha)
type FillColor = Color
type StrokeColor = Color
type FillThickness = GraphicalNumeric
type StrokeLineThickness = GraphicalNumeric
type UpperLeft = Point
type UpperRight = Point
type LowerLeft = Point
type LowerRight = Point
type NumberOfPoints = Int
type FontFamily = [Char]
type FontSize = GraphicalNumeric
data BasicShapesOut = DrawShapes CanvasId [Shape]
deriving (Show, Eq, Generic, NFData)
data Shape = CompositeShape { shapes :: [Shape]
, positionM :: Maybe Position
, rotationM :: Maybe Rotation
}
| Rectangle { position :: Position
, dimensions :: Dimensions
, fillColor :: FillColor
, strokeLineThickness :: StrokeLineThickness
, strokeColor :: StrokeColor
, rotationM :: Maybe Rotation
}
| Circle { position :: Position
, radius :: Radius
, fillColor :: FillColor
, strokeLineThickness :: StrokeLineThickness
, strokeColor :: StrokeColor
, rotationM :: Maybe Rotation
}
| RegularPolygon { position :: Position
, numberOfPoints :: NumberOfPoints
, radius :: Radius
, fillColor :: FillColor
, strokeLineThickness :: StrokeLineThickness
, strokeColor :: StrokeColor
, rotationM :: Maybe Rotation
}
| Text { text :: [Char]
, fontFamily :: FontFamily
, fontSize :: FontSize
, position :: Position
, alignment :: Alignment
, fillColor :: FillColor
, strokeLineThickness :: StrokeLineThickness
, strokeColor :: StrokeColor
, rotationM :: Maybe Rotation
}
| Line { point1 :: Point
, point2 :: Point
, strokeLineThickness :: StrokeLineThickness
, strokeColor :: StrokeColor
, rotationM :: Maybe Rotation
}
| MultiLine { points :: [Point]
, strokeLineThickness :: StrokeLineThickness
, strokeColor :: StrokeColor
, rotationM :: Maybe Rotation
}
| FilledMultiLine { points :: [Point]
, fillWidth :: FillThickness
, fillColor :: FillColor
, strokeLineThickness :: StrokeLineThickness
, strokeColor :: StrokeColor
, rotationM :: Maybe Rotation
}
| Polygon { points :: [Point]
, fillColor :: FillColor
, strokeLineThickness :: StrokeLineThickness
, strokeColor :: StrokeColor
, rotationM :: Maybe Rotation
}
deriving (Show, Eq, Generic, NFData)
data Rotation = Rotation RotatePoint Angle
deriving (Show, Eq, Generic, NFData)
data RotatePoint = AroundCenter
| AroundPoint Point
deriving (Show, Eq, Generic, NFData)
data BoundingBox = BoundingBox LowerLeft UpperLeft UpperRight LowerRight
deriving (Show, Eq)