Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- setupBasicShapesModuleConfiguration :: EventloopSetupModuleConfiguration
- basicShapesModuleIdentifier :: EventloopModuleIdentifier
- basicShapesPostProcessor :: PostProcessor
- data BoundingBox = BoundingBox LowerLeft UpperLeft UpperRight LowerRight
- data RotatePoint
- data Rotation = Rotation RotatePoint Angle
- data Shape
- = CompositeShape { }
- | Rectangle { }
- | Circle { }
- | RegularPolygon { }
- | Text { }
- | Line { }
- | MultiLine { }
- | FilledMultiLine { }
- | Polygon { }
- data BasicShapesOut = DrawShapes CanvasId [Shape]
- type FontSize = GraphicalNumeric
- type FontFamily = [Char]
- type NumberOfPoints = Int
- type LowerRight = Point
- type LowerLeft = Point
- type UpperRight = Point
- type UpperLeft = Point
- type StrokeLineThickness = GraphicalNumeric
- type FillThickness = GraphicalNumeric
- type StrokeColor = Color
- type FillColor = Color
- type Color = (Red, Green, Blue, Alpha)
- type Alpha = GraphicalNumeric
- type Blue = GraphicalNumeric
- type Green = GraphicalNumeric
- type Red = GraphicalNumeric
- type Radius = GraphicalNumeric
- type Dimensions = (Width, Height)
- type Height = GraphicalNumeric
- type Width = GraphicalNumeric
- type Position = Point
- type GraphicalNumeric = Float
- type CanvasId = NumericId
- data Alignment
- data GeometricPrimitive
- = Points [Point]
- | CircleArea Point Radius
- opOnBoundingBox :: (Point -> Point) -> BoundingBox -> BoundingBox
- allRegularPolygonPoints :: NumberOfPoints -> Point -> Radius -> [Point]
- boundingBoxFromPrimitives :: [GeometricPrimitive] -> BoundingBox
- normalizeBBox :: BoundingBox -> BoundingBox
- roundPoint :: Point -> ScreenPoint
- roundColor :: Color -> ScreenColor
- strokePointsForLine :: StrokeLineThickness -> Point -> Point -> [Point]
- strokePointsForConnection :: StrokeLineThickness -> Point -> Point -> Point -> [Point]
- strokePoints :: StrokeLineThickness -> [Point] -> [Point]
- strokePointsClosedPath :: StrokeLineThickness -> [Point] -> [Point]
- class ToPrimitives a where
- toPrimitives :: a -> [GeometricPrimitive]
- class ToCenter a where
- class ToPrimitives a => ToBoundingBox a where
- toBoundingBox :: a -> BoundingBox
- class ToBoundingBox a => Overlaps a where
- findRotationPoint :: ToCenter a => a -> Rotation -> Point
- class ToCanvasOut a where
- toCanvasOut :: a -> CanvasOut
- class ToCanvasOperations a where
- toCanvasOperations :: a -> [CanvasOperation]
- toCanvasText :: Shape -> CanvasText
- class ToScreenPathPart a where
- toScreenPathParts :: a -> Maybe ([ScreenPathPart], ScreenStartingPoint)
- toCanvasPathFill :: Shape -> PathFill
- hasCanvasPathFill :: Shape -> Bool
- allScreenPolygonPoints :: Shape -> [Point]
Documentation
data BoundingBox Source #
BoundingBox LowerLeft UpperLeft UpperRight LowerRight | | The point indications are from the perspective of a regular Cartesian coördinate system. |
Instances
data RotatePoint Source #
Instances
Rotation RotatePoint Angle | | Rotation is around a point on the canvas. May be the centre of the boundingbox (enclosing rectangle) or an arbitrary point. Angle is in degrees and counter-clockwise in the coördinate system(from the x-axis to the y-axis) and visually on canvas clock-wise. |
Instances
Eq Rotation Source # | |
Show Rotation Source # | |
Generic Rotation Source # | |
NFData Rotation Source # | |
Defined in Eventloop.Module.BasicShapes.Types | |
type Rep Rotation Source # | |
Defined in Eventloop.Module.BasicShapes.Types type Rep Rotation = D1 (MetaData "Rotation" "Eventloop.Module.BasicShapes.Types" "eventloop-0.8.2.8-inplace" False) (C1 (MetaCons "Rotation" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RotatePoint) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Angle))) |
CompositeShape | Should contain atleast 1 shape. Rotation before Position |
Rectangle | | Position is upperleftcorner. Position is the corner closes to origin. Visually in canvas, this is top left. In a Cartesian coördinate system, this is bottom left. |
Circle | | Position is center |
RegularPolygon | The first point of the regular polygon, always starts in the direction from the x-axis.(Towards x-infinity). Position is the the centre of the regular polygon |
Text | |
| |
Line | |
MultiLine | |
| |
FilledMultiLine | |
| |
Polygon | |
|
Instances
data BasicShapesOut Source #
Instances
type FontSize = GraphicalNumeric Source #
type FontFamily = [Char] Source #
type NumberOfPoints = Int Source #
type LowerRight = Point Source #
type UpperRight = Point Source #
type FillThickness = GraphicalNumeric Source #
type StrokeColor = Color Source #
type Alpha = GraphicalNumeric Source #
type Blue = GraphicalNumeric Source #
type Green = GraphicalNumeric Source #
type Red = GraphicalNumeric Source #
type Radius = GraphicalNumeric Source #
type Dimensions = (Width, Height) Source #
type Height = GraphicalNumeric Source #
type Width = GraphicalNumeric Source #
type GraphicalNumeric = Float Source #
Opcode: 1500
AlignLeft | Opcode: 1501 |
AlignRight | Opcode: 1502 |
AlignCenter | Opcode: 1503 |
Instances
Eq Alignment Source # | |
Show Alignment Source # | |
Generic Alignment Source # | |
NFData Alignment Source # | |
Defined in Eventloop.Module.Websocket.Canvas.Types | |
FromJSON Alignment | |
Defined in Eventloop.Module.Websocket.Canvas.JSONEncoding parseJSON :: Value -> Parser Alignment parseJSONList :: Value -> Parser [Alignment] | |
ToJSON Alignment | |
Defined in Eventloop.Module.Websocket.Canvas.JSONEncoding toEncoding :: Alignment -> Encoding toJSONList :: [Alignment] -> Value toEncodingList :: [Alignment] -> Encoding | |
type Rep Alignment Source # | |
Defined in Eventloop.Module.Websocket.Canvas.Types type Rep Alignment = D1 (MetaData "Alignment" "Eventloop.Module.Websocket.Canvas.Types" "eventloop-0.8.2.8-inplace" False) (C1 (MetaCons "AlignLeft" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "AlignRight" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AlignCenter" PrefixI False) (U1 :: Type -> Type))) |
data GeometricPrimitive Source #
Instances
Eq GeometricPrimitive Source # | |
Defined in Eventloop.Module.BasicShapes.Classes (==) :: GeometricPrimitive -> GeometricPrimitive -> Bool # (/=) :: GeometricPrimitive -> GeometricPrimitive -> Bool # | |
Show GeometricPrimitive Source # | |
Defined in Eventloop.Module.BasicShapes.Classes showsPrec :: Int -> GeometricPrimitive -> ShowS # show :: GeometricPrimitive -> String # showList :: [GeometricPrimitive] -> ShowS # | |
RotateLeftAround GeometricPrimitive Source # | |
Defined in Eventloop.Module.BasicShapes.Classes rotateLeftAround :: Point -> Angle -> GeometricPrimitive -> GeometricPrimitive Source # | |
Translate GeometricPrimitive Source # | |
Defined in Eventloop.Module.BasicShapes.Classes | |
ExtremaCoord GeometricPrimitive Source # | |
Defined in Eventloop.Module.BasicShapes.Classes xMin :: GeometricPrimitive -> X Source # xMax :: GeometricPrimitive -> X Source # yMin :: GeometricPrimitive -> Y Source # yMax :: GeometricPrimitive -> Y Source # |
opOnBoundingBox :: (Point -> Point) -> BoundingBox -> BoundingBox Source #
allRegularPolygonPoints :: NumberOfPoints -> Point -> Radius -> [Point] Source #
roundPoint :: Point -> ScreenPoint Source #
roundColor :: Color -> ScreenColor Source #
strokePointsForLine :: StrokeLineThickness -> Point -> Point -> [Point] Source #
strokePointsForConnection :: StrokeLineThickness -> Point -> Point -> Point -> [Point] Source #
strokePoints :: StrokeLineThickness -> [Point] -> [Point] Source #
strokePointsClosedPath :: StrokeLineThickness -> [Point] -> [Point] Source #
class ToPrimitives a where Source #
toPrimitives :: a -> [GeometricPrimitive] Source #
Instances
ToPrimitives BoundingBox Source # | |
Defined in Eventloop.Module.BasicShapes.Classes toPrimitives :: BoundingBox -> [GeometricPrimitive] Source # | |
ToPrimitives Shape Source # | |
Defined in Eventloop.Module.BasicShapes.Classes toPrimitives :: Shape -> [GeometricPrimitive] Source # | |
ToPrimitives StatefulBB Source # | |
Defined in Eventloop.Module.StatefulGraphics.Types toPrimitives :: StatefulBB -> [GeometricPrimitive] Source # | |
ToPrimitives StatefulGraphic Source # | |
Defined in Eventloop.Module.StatefulGraphics.Types |
class ToCenter a where Source #
Instances
ToCenter BoundingBox Source # | |
Defined in Eventloop.Module.BasicShapes.Classes toCenter :: BoundingBox -> Point Source # | |
ToCenter Shape Source # | |
class ToPrimitives a => ToBoundingBox a where Source #
toBoundingBox :: a -> BoundingBox Source #
Instances
class ToBoundingBox a => Overlaps a where Source #
Nothing
Instances
class ToCanvasOut a where Source #
toCanvasOut :: a -> CanvasOut Source #
Instances
ToCanvasOut BasicShapesOut Source # | |
Defined in Eventloop.Module.BasicShapes.Classes |
class ToCanvasOperations a where Source #
toCanvasOperations :: a -> [CanvasOperation] Source #
Instances
ToCanvasOperations Shape Source # | |
Defined in Eventloop.Module.BasicShapes.Classes toCanvasOperations :: Shape -> [CanvasOperation] Source # |
toCanvasText :: Shape -> CanvasText Source #
class ToScreenPathPart a where Source #
toScreenPathParts :: a -> Maybe ([ScreenPathPart], ScreenStartingPoint) Source #
Instances
ToScreenPathPart Shape Source # | |
Defined in Eventloop.Module.BasicShapes.Classes toScreenPathParts :: Shape -> Maybe ([ScreenPathPart], ScreenStartingPoint) Source # |
toCanvasPathFill :: Shape -> PathFill Source #
hasCanvasPathFill :: Shape -> Bool Source #
allScreenPolygonPoints :: Shape -> [Point] Source #