Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- setupGraphsModuleConfiguration :: EventloopSetupModuleConfiguration
- graphsModuleIdentifier :: EventloopModuleIdentifier
- nodeRadius :: Float
- textSize :: Float
- textFont :: [Char]
- xArrowSize :: Float
- yArrowSize :: Float
- weightHeight :: Float
- dimCanvasGraphs :: (Float, Float)
- roundDimCanvasGraphs :: (Int, Int)
- canvasGraphsWidth :: Float
- canvasGraphsHeight :: Float
- instructionsHeight :: Float
- instructionsBeginAt :: Float
- canvasInstrWidth :: Float
- canvasInstrHeight :: Float
- dimCanvasInstr :: (Float, Float)
- roundDimCanvasInstr :: (Int, Int)
- canvasIdGraphs :: CanvasId
- canvasIdInstructions :: CanvasId
- onNode :: [Node] -> Pos -> Maybe Node
- graphsPreProcessor :: PreProcessor
- graphsPostProcessor :: PostProcessor
- colorToRGBAColor :: Color -> Color
- thicknessToFloat :: Thickness -> StrokeLineThickness
- findNode :: [Node] -> Label -> Node
- graphToShapes :: Graph -> [Shape]
- nodeToShapes :: Node -> [Shape]
- edgeToShapes :: Node -> Node -> Edge -> Directed -> Weighted -> [Shape]
- posOnVector :: Float -> Vector -> Pos -> Pos
- vectorize :: Pos -> Pos -> Vector
- downPerpendicularTo :: Pos -> Pos -> Vector
- upPerpendicularTo :: Pos -> Pos -> Vector
- vectorSize :: Vector -> Float
- data Weighted
- data Directed
- data Thickness
- data Color
- data Graph = Graph {}
- type Edge = (Label, Label, Color, Weight, Thickness)
- type Node = (Label, Pos, Color)
- type Weight = Float
- type Label = Char
- data GraphsOut
- data GraphsIn
- = Mouse MouseEvent Pos
- | Key [Char]
- type Vector = (Float, Float)
- type Pos = (Float, Float)
- data MouseEvent
- data MouseButton
Documentation
nodeRadius :: Float Source #
xArrowSize :: Float Source #
yArrowSize :: Float Source #
weightHeight :: Float Source #
dimCanvasGraphs :: (Float, Float) Source #
roundDimCanvasGraphs :: (Int, Int) Source #
dimCanvasInstr :: (Float, Float) Source #
roundDimCanvasInstr :: (Int, Int) Source #
onNode :: [Node] -> Pos -> Maybe Node Source #
Checkes to see if there is a node on a certain position
graphsPreProcessor :: PreProcessor Source #
Abstracts the standardized EventTypes
to GraphsIn
graphsPostProcessor :: PostProcessor Source #
Abstracts GraphsOut
back to BasicShapes
and Canvas
events
colorToRGBAColor :: Color -> Color Source #
Translates color datatype to RGBA codes
thicknessToFloat :: Thickness -> StrokeLineThickness Source #
Translates the thickness to a float
graphToShapes :: Graph -> [Shape] Source #
nodeToShapes :: Node -> [Shape] Source #
posOnVector :: Float -> Vector -> Pos -> Pos Source #
Returns the point when making a step f long from the point start in the direction of the vector. The length between start pos and result pos is always f.
downPerpendicularTo :: Pos -> Pos -> Vector Source #
Returns the vector perpendicular on the given vector between the 2 points. Always has positive y and vector length 1; y is inverted in canvas
upPerpendicularTo :: Pos -> Pos -> Vector Source #
Returns the vector perpendicular on the given vector between the 2 points. Always has negative y and vector length 1; y is inverted in canvas
vectorSize :: Vector -> Float Source #
Returns the size of the vector
Instances
Eq Color Source # | |
Show Color Source # | |
Generic Color Source # | |
NFData Color Source # | |
Defined in Eventloop.Module.Graphs.Types | |
type Rep Color Source # | |
Defined in Eventloop.Module.Graphs.Types type Rep Color = D1 (MetaData "Color" "Eventloop.Module.Graphs.Types" "eventloop-0.8.2.8-inplace" False) (((C1 (MetaCons "Red" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Blue" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Green" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Purple" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Grey" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Yellow" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Orange" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Black" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "White" PrefixI False) (U1 :: Type -> Type))))) |
Instances
Eq Graph Source # | |
Show Graph Source # | |
Generic Graph Source # | |
NFData Graph Source # | |
Defined in Eventloop.Module.Graphs.Types | |
type Rep Graph Source # | |
Defined in Eventloop.Module.Graphs.Types type Rep Graph = D1 (MetaData "Graph" "Eventloop.Module.Graphs.Types" "eventloop-0.8.2.8-inplace" False) (C1 (MetaCons "Graph" PrefixI True) ((S1 (MetaSel (Just "nodes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node]) :*: S1 (MetaSel (Just "edges") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Edge])) :*: (S1 (MetaSel (Just "directed") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Directed) :*: S1 (MetaSel (Just "weighted") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Weighted)))) |
Instances
Eq GraphsOut Source # | |
Show GraphsOut Source # | |
Generic GraphsOut Source # | |
NFData GraphsOut Source # | |
Defined in Eventloop.Module.Graphs.Types | |
type Rep GraphsOut Source # | |
Defined in Eventloop.Module.Graphs.Types type Rep GraphsOut = D1 (MetaData "GraphsOut" "Eventloop.Module.Graphs.Types" "eventloop-0.8.2.8-inplace" False) (C1 (MetaCons "SetupGraphs" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "DrawGraph" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Graph)) :+: C1 (MetaCons "Instructions" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String])))) |
data MouseEvent Source #
Click MouseButton | |
DoubleClick MouseButton | |
MouseMove | |
MouseDown MouseButton | |
MouseUp MouseButton | |
MouseEnter | |
MouseLeave |
Instances
Eq MouseEvent Source # | |
Defined in Eventloop.Module.Websocket.Mouse.Types (==) :: MouseEvent -> MouseEvent -> Bool # (/=) :: MouseEvent -> MouseEvent -> Bool # | |
Show MouseEvent Source # | |
Defined in Eventloop.Module.Websocket.Mouse.Types showsPrec :: Int -> MouseEvent -> ShowS # show :: MouseEvent -> String # showList :: [MouseEvent] -> ShowS # | |
FromJSON MouseEvent | |
Defined in Eventloop.Module.Websocket.Mouse.Mouse parseJSON :: Value -> Parser MouseEvent parseJSONList :: Value -> Parser [MouseEvent] |
data MouseButton Source #