Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data LineAnchorsForRender = LineAnchorsForRender {}
- lineAnchorsForRender_doesIntersectPoint :: LineAnchorsForRender -> XY -> Bool
- lineAnchorsForRender_doesIntersectBox :: LineAnchorsForRender -> LBox -> Bool
- lineAnchorsForRender_findIntersectingSubsegment :: LineAnchorsForRender -> XY -> Maybe Int
- lineAnchorsForRender_length :: LineAnchorsForRender -> Int
- sAutoLine_to_lineAnchorsForRenderList :: HasOwlTree a => a -> SAutoLine -> [LineAnchorsForRender]
- sSimpleLineNewRenderFn :: SAutoLine -> Maybe LineAnchorsForRender -> SEltDrawer
- sSimpleLineNewRenderFnComputeCache :: HasOwlTree a => a -> SAutoLine -> LineAnchorsForRender
- getSAutoLineLabelPosition :: HasOwlTree a => a -> SAutoLine -> SAutoLineLabel -> XY
- getSAutoLineLabelPositionFromLineAnchorsForRender :: LineAnchorsForRender -> SAutoLine -> SAutoLineLabel -> XY
- getSortedSAutoLineLabelPositions :: HasOwlTree a => a -> SAutoLine -> [(XY, Int, SAutoLineLabel)]
- getClosestPointOnLineFromLineAnchorsForRenderList :: [LineAnchorsForRender] -> XY -> (XY, Int, Float)
- data CartDir
- class TransformMe a where
- transformMe_rotateLeft :: a -> a
- transformMe_rotateRight :: a -> a
- transformMe_reflectHorizontally :: a -> a
- transformMe_reflectVertically :: a -> a
- determineSeparation :: (LBox, (Int, Int, Int, Int)) -> (LBox, (Int, Int, Int, Int)) -> (Bool, Bool)
- lineAnchorsForRender_simplify :: LineAnchorsForRender -> LineAnchorsForRender
- internal_getSAutoLineLabelPosition_walk :: LineAnchorsForRender -> Int -> XY
Documentation
data LineAnchorsForRender Source #
Instances
sAutoLine_to_lineAnchorsForRenderList :: HasOwlTree a => a -> SAutoLine -> [LineAnchorsForRender] Source #
sSimpleLineNewRenderFnComputeCache :: HasOwlTree a => a -> SAutoLine -> LineAnchorsForRender Source #
getSAutoLineLabelPosition :: HasOwlTree a => a -> SAutoLine -> SAutoLineLabel -> XY Source #
getSAutoLineLabelPositionFromLineAnchorsForRender :: LineAnchorsForRender -> SAutoLine -> SAutoLineLabel -> XY Source #
getSortedSAutoLineLabelPositions :: HasOwlTree a => a -> SAutoLine -> [(XY, Int, SAutoLineLabel)] Source #
getClosestPointOnLineFromLineAnchorsForRenderList :: [LineAnchorsForRender] -> XY -> (XY, Int, Float) Source #
exposed for testing
Instances
Generic CartDir Source # | |
Show CartDir Source # | |
NFData CartDir Source # | |
Defined in Potato.Flow.Methods.LineTypes | |
Eq CartDir Source # | |
TransformMe CartDir Source # | |
type Rep CartDir Source # | |
Defined in Potato.Flow.Methods.LineTypes type Rep CartDir = D1 ('MetaData "CartDir" "Potato.Flow.Methods.LineTypes" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'False) ((C1 ('MetaCons "CD_Up" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CD_Down" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CD_Left" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CD_Right" 'PrefixI 'False) (U1 :: Type -> Type))) |
class TransformMe a where Source #
Nothing
transformMe_rotateLeft :: a -> a Source #
transformMe_rotateRight :: a -> a Source #
transformMe_reflectHorizontally :: a -> a Source #
transformMe_reflectVertically :: a -> a Source #