sifflet-lib-1.0: Library of modules shared by sifflet and its tests and its exporters.Source codeContentsIndex
Sifflet.Data.TreeLayout
Synopsis
data VColor
= ColorRGB Double Double Double
| ColorRGBA Double Double Double Double
white :: VColor
cream :: VColor
black :: VColor
lightBlue :: VColor
lightBlueGreen :: VColor
lightGray :: VColor
mediumGray :: VColor
darkGray :: VColor
yellow :: VColor
darkBlueGreen :: VColor
blueGreen :: VColor
data Style = Style {
styleFont :: VFont
lineWidth :: Double
textMargin :: Double
hpad :: Double
vpad :: Double
exomargin :: Double
vtinypad :: (Double, Double)
styleFramePad :: Double
styleNormalTextColor :: VColor
styleNormalFillColor :: VColor
styleNormalEdgeColor :: VColor
styleActiveTextColor :: VColor
styleActiveFillColor :: VColor
styleActiveEdgeColor :: VColor
styleSelectedTextColor :: VColor
styleSelectedFillColor :: VColor
styleSelectedEdgeColor :: VColor
styleTetherColor :: VColor
styleAuxOffset :: Position
styleAuxColor :: VColor
styleAuxFont :: VFont
styleIoletRadius :: Double
styleShowNodeBoxes :: Bool
styleShowNodePorts :: Bool
}
data VFont = VFont {
vfontFace :: String
vfontSlant :: FontSlant
vfontWeight :: FontWeight
vfontSize :: Double
}
defaultStyle :: Style
style0 :: Style
style1 :: Style
style2 :: Style
style3 :: Style
wstyle :: Style
styleIncreasePadding :: Style -> Double -> Style
data FontTextExtents = FontTextExtents {
fontAscent :: Double
fontDescent :: Double
fontHeight :: Double
fontMaxXadvance :: Double
fontMaxYadvance :: Double
textXbearing :: Double
textYbearing :: Double
extTextWidth :: Double
extTextHeight :: Double
textXadvance :: Double
textYadvance :: Double
}
setFont :: VFont -> Render ()
measureText :: Style -> String -> Size
styleTextExtents :: Style -> String -> FontTextExtents
ftExtents :: String -> Render FontTextExtents
data TextBox = TextBox {
tbText :: String
tbTextBB :: BBox
tbBoxBB :: BBox
}
makeTextBox :: Style -> String -> TextBox
tbWidth :: TextBox -> Double
tbHeight :: TextBox -> Double
tbBottom :: TextBox -> Double
tbCenter :: TextBox -> Position
tbTextCenter :: TextBox -> Position
tbBoxCenter :: TextBox -> Position
offsetTextBoxCenters :: Position -> TextBox -> TextBox -> TextBox
tbSetWidth :: TextBox -> Double -> TextBox
treeSizes :: Style -> Tree (GNode e) -> Tree Size
data GNode e = GNode {
gnodeValue :: e
gnodeTextBoxes :: [TextBox]
gnodeNodeBB :: BBox
gnodeInlets :: [Iolet]
gnodeOutlets :: [Iolet]
}
treeGNodes :: Repr e => Style -> IoletCounter e -> Tree e -> Tree (GNode e)
gnodeText :: GNode e -> String
gnodeTextBB :: GNode e -> BBox
data Iolet = Iolet Circle
ioletCenter :: Iolet -> Position
makeIolets :: Style -> BBox -> (Int, Int) -> ([Iolet], [Iolet])
makeIoletsRow :: Style -> Double -> Double -> Int -> [Iolet]
pointInIolet :: Position -> Iolet -> Bool
type IoletCounter e = e -> (Int, Int)
zeroIoletCounter :: IoletCounter e
makeGNode :: Repr e => Style -> IoletCounter e -> e -> GNode e
type TreeLayout e = Tree (LayoutNode e)
data LayoutNode e = LayoutNode {
nodeGNode :: GNode e
nodeTreeBB :: BBox
}
layoutNodeSource :: LayoutNode e -> e
layoutRootBB :: TreeLayout e -> BBox
layoutTreeBB :: TreeLayout e -> BBox
treeLayout :: Repr e => Style -> IoletCounter e -> Tree e -> TreeLayout e
treeLayoutPaddedSize :: Style -> TreeLayout e -> Size
treeLayoutSize :: TreeLayout e -> Size
treeLayoutWidth :: TreeLayout e -> Double
layoutTreeMoveCenterTo :: Double -> Double -> TreeLayout e -> TreeLayout e
pointInLayoutNode :: Position -> LayoutNode e -> Bool
pointInGNode :: Position -> GNode e -> Bool
findRect :: Position -> TreeLayout e -> Maybe Rectangle
treeLayoutWiden :: TreeLayout e -> Double -> TreeLayout e
Documentation
data VColor Source
Constructors
ColorRGB Double Double Double
ColorRGBA Double Double Double Double
white :: VColorSource
cream :: VColorSource
black :: VColorSource
lightBlue :: VColorSource
lightBlueGreen :: VColorSource
lightGray :: VColorSource
mediumGray :: VColorSource
darkGray :: VColorSource
yellow :: VColorSource
darkBlueGreen :: VColorSource
blueGreen :: VColorSource
data Style Source
Constructors
Style
styleFont :: VFont
lineWidth :: Double
textMargin :: Double
hpad :: Double
vpad :: Double
exomargin :: Double
vtinypad :: (Double, Double)
styleFramePad :: Double
styleNormalTextColor :: VColor
styleNormalFillColor :: VColor
styleNormalEdgeColor :: VColor
styleActiveTextColor :: VColor
styleActiveFillColor :: VColor
styleActiveEdgeColor :: VColor
styleSelectedTextColor :: VColor
styleSelectedFillColor :: VColor
styleSelectedEdgeColor :: VColor
styleTetherColor :: VColor
styleAuxOffset :: Position
styleAuxColor :: VColor
styleAuxFont :: VFont
styleIoletRadius :: Double
styleShowNodeBoxes :: Bool
styleShowNodePorts :: Bool
data VFont Source
Constructors
VFont
vfontFace :: String
vfontSlant :: FontSlant
vfontWeight :: FontWeight
vfontSize :: Double
defaultStyle :: StyleSource
style0 :: StyleSource
style1 :: StyleSource
style2 :: StyleSource
style3 :: StyleSource
wstyle :: StyleSource
styleIncreasePadding :: Style -> Double -> StyleSource
data FontTextExtents Source
Constructors
FontTextExtents
fontAscent :: Double
fontDescent :: Double
fontHeight :: Double
fontMaxXadvance :: Double
fontMaxYadvance :: Double
textXbearing :: Double
textYbearing :: Double
extTextWidth :: Double
extTextHeight :: Double
textXadvance :: Double
textYadvance :: Double
show/hide Instances
setFont :: VFont -> Render ()Source
measureText :: Style -> String -> SizeSource
styleTextExtents :: Style -> String -> FontTextExtentsSource
ftExtents :: String -> Render FontTextExtentsSource
ftExtents: used for what?
data TextBox Source
Constructors
TextBox
tbText :: String
tbTextBB :: BBox
tbBoxBB :: BBox
show/hide Instances
makeTextBox :: Style -> String -> TextBoxSource
tbWidth :: TextBox -> DoubleSource
tbHeight :: TextBox -> DoubleSource
tbBottom :: TextBox -> DoubleSource
tbCenter :: TextBox -> PositionSource
tbTextCenter :: TextBox -> PositionSource
tbBoxCenter :: TextBox -> PositionSource
offsetTextBoxCenters :: Position -> TextBox -> TextBox -> TextBoxSource
tbSetWidth :: TextBox -> Double -> TextBoxSource
treeSizes :: Style -> Tree (GNode e) -> Tree SizeSource
data GNode e Source
Constructors
GNode
gnodeValue :: e
gnodeTextBoxes :: [TextBox]
gnodeNodeBB :: BBox
gnodeInlets :: [Iolet]
gnodeOutlets :: [Iolet]
show/hide Instances
Eq e => Eq (GNode e)
Show e => Show (GNode e)
Translate (GNode e)
Draw (GNode e)
treeGNodes :: Repr e => Style -> IoletCounter e -> Tree e -> Tree (GNode e)Source
gnodeText :: GNode e -> StringSource
gnodeTextBB :: GNode e -> BBoxSource
data Iolet Source
An Iolet is a circular port. Other shapes could be added.
Constructors
Iolet Circle
show/hide Instances
ioletCenter :: Iolet -> PositionSource
makeIolets :: Style -> BBox -> (Int, Int) -> ([Iolet], [Iolet])Source
makeIoletsRow :: Style -> Double -> Double -> Int -> [Iolet]Source
pointInIolet :: Position -> Iolet -> BoolSource
type IoletCounter e = e -> (Int, Int)Source
zeroIoletCounter :: IoletCounter eSource
makeGNode :: Repr e => Style -> IoletCounter e -> e -> GNode eSource
type TreeLayout e = Tree (LayoutNode e)Source
data LayoutNode e Source
Constructors
LayoutNode
nodeGNode :: GNode e
nodeTreeBB :: BBox
show/hide Instances
layoutNodeSource :: LayoutNode e -> eSource
layoutRootBB :: TreeLayout e -> BBoxSource
layoutTreeBB :: TreeLayout e -> BBoxSource
treeLayout :: Repr e => Style -> IoletCounter e -> Tree e -> TreeLayout eSource
treeLayoutPaddedSize :: Style -> TreeLayout e -> SizeSource
treeLayoutSize :: TreeLayout e -> SizeSource
treeLayoutWidth :: TreeLayout e -> DoubleSource
layoutTreeMoveCenterTo :: Double -> Double -> TreeLayout e -> TreeLayout eSource
pointInLayoutNode :: Position -> LayoutNode e -> BoolSource
pointInGNode :: Position -> GNode e -> BoolSource
findRect :: Position -> TreeLayout e -> Maybe RectangleSource
treeLayoutWiden :: TreeLayout e -> Double -> TreeLayout eSource
Produced by Haddock version 2.6.1