Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module provides the core widget combinators and rendering routines. Everything this library does is in terms of these basic primitives.
Synopsis
- class TextWidth a where
- emptyWidget :: Widget n
- raw :: Image -> Widget n
- txt :: Text -> Widget n
- txtWrap :: Text -> Widget n
- txtWrapWith :: WrapSettings -> Text -> Widget n
- str :: String -> Widget n
- strWrap :: String -> Widget n
- strWrapWith :: WrapSettings -> String -> Widget n
- fill :: Char -> Widget n
- hyperlink :: Text -> Widget n -> Widget n
- data Padding
- padLeft :: Padding -> Widget n -> Widget n
- padRight :: Padding -> Widget n -> Widget n
- padTop :: Padding -> Widget n -> Widget n
- padBottom :: Padding -> Widget n -> Widget n
- padLeftRight :: Int -> Widget n -> Widget n
- padTopBottom :: Int -> Widget n -> Widget n
- padAll :: Int -> Widget n -> Widget n
- (<=>) :: Widget n -> Widget n -> Widget n
- (<+>) :: Widget n -> Widget n -> Widget n
- hBox :: [Widget n] -> Widget n
- vBox :: [Widget n] -> Widget n
- hLimit :: Int -> Widget n -> Widget n
- hLimitPercent :: Int -> Widget n -> Widget n
- vLimit :: Int -> Widget n -> Widget n
- vLimitPercent :: Int -> Widget n -> Widget n
- setAvailableSize :: (Int, Int) -> Widget n -> Widget n
- withDefAttr :: AttrName -> Widget n -> Widget n
- modifyDefAttr :: (Attr -> Attr) -> Widget n -> Widget n
- withAttr :: AttrName -> Widget n -> Widget n
- forceAttr :: AttrName -> Widget n -> Widget n
- forceAttrAllowStyle :: AttrName -> Widget n -> Widget n
- overrideAttr :: AttrName -> AttrName -> Widget n -> Widget n
- updateAttrMap :: (AttrMap -> AttrMap) -> Widget n -> Widget n
- withBorderStyle :: BorderStyle -> Widget n -> Widget n
- joinBorders :: Widget n -> Widget n
- separateBorders :: Widget n -> Widget n
- freezeBorders :: Widget n -> Widget n
- showCursor :: n -> Location -> Widget n -> Widget n
- putCursor :: n -> Location -> Widget n -> Widget n
- class Named a n where
- getName :: a -> n
- translateBy :: Location -> Widget n -> Widget n
- relativeTo :: Ord n => n -> Location -> Widget n -> Widget n
- cropLeftBy :: Int -> Widget n -> Widget n
- cropRightBy :: Int -> Widget n -> Widget n
- cropTopBy :: Int -> Widget n -> Widget n
- cropBottomBy :: Int -> Widget n -> Widget n
- cropLeftTo :: Int -> Widget n -> Widget n
- cropRightTo :: Int -> Widget n -> Widget n
- cropTopTo :: Int -> Widget n -> Widget n
- cropBottomTo :: Int -> Widget n -> Widget n
- reportExtent :: Ord n => n -> Widget n -> Widget n
- clickable :: Ord n => n -> Widget n -> Widget n
- viewport :: (Ord n, Show n) => n -> ViewportType -> Widget n -> Widget n
- visible :: Widget n -> Widget n
- visibleRegion :: Location -> DisplayRegion -> Widget n -> Widget n
- unsafeLookupViewport :: Ord n => n -> RenderM n (Maybe Viewport)
- cached :: Ord n => n -> Widget n -> Widget n
- withVScrollBars :: VScrollBarOrientation -> Widget n -> Widget n
- withHScrollBars :: HScrollBarOrientation -> Widget n -> Widget n
- withClickableHScrollBars :: (ClickableScrollbarElement -> n -> n) -> Widget n -> Widget n
- withClickableVScrollBars :: (ClickableScrollbarElement -> n -> n) -> Widget n -> Widget n
- withVScrollBarHandles :: Widget n -> Widget n
- withHScrollBarHandles :: Widget n -> Widget n
- withVScrollBarRenderer :: VScrollbarRenderer n -> Widget n -> Widget n
- withHScrollBarRenderer :: HScrollbarRenderer n -> Widget n -> Widget n
- data VScrollbarRenderer n = VScrollbarRenderer {}
- data HScrollbarRenderer n = HScrollbarRenderer {}
- verticalScrollbarRenderer :: VScrollbarRenderer n
- horizontalScrollbarRenderer :: HScrollbarRenderer n
- scrollbarAttr :: AttrName
- scrollbarTroughAttr :: AttrName
- scrollbarHandleAttr :: AttrName
- verticalScrollbar :: Ord n => VScrollbarRenderer n -> VScrollBarOrientation -> n -> Maybe (ClickableScrollbarElement -> n -> n) -> Bool -> Int -> Int -> Int -> Widget n
- horizontalScrollbar :: Ord n => HScrollbarRenderer n -> HScrollBarOrientation -> n -> Maybe (ClickableScrollbarElement -> n -> n) -> Bool -> Int -> Int -> Int -> Widget n
- addResultOffset :: Location -> Result n -> Result n
- cropToContext :: Widget n -> Widget n
Basic rendering primitives
emptyWidget :: Widget n Source #
The empty widget.
txt :: Text -> Widget n Source #
Build a widget from a Text
value. Breaks newlines up and
space-pads short lines out to the length of the longest line.
The input string must not contain tab characters. If it does, interface corruption will result since the terminal will likely render it as taking up more than a single column. The caller should replace tabs with the appropriate number of spaces as desired. The input text should not contain escape sequences or carriage returns.
txtWrap :: Text -> Widget n Source #
Make a widget from text, but wrap the words in the input's lines at the available width using the default wrapping settings. The input text should not contain escape sequences or carriage returns.
Unlike txt
, this is greedy horizontally.
txtWrapWith :: WrapSettings -> Text -> Widget n Source #
Make a widget from text, but wrap the words in the input's lines at the available width using the specified wrapping settings. The input text should not contain escape sequences or carriage returns.
Unlike txt
, this is greedy horizontally.
str :: String -> Widget n Source #
Build a widget from a String
. Behaves the same as txt
when the
input contains multiple lines.
The input string must not contain tab characters. If it does, interface corruption will result since the terminal will likely render it as taking up more than a single column. The caller should replace tabs with the appropriate number of spaces as desired. The input string should not contain escape sequences or carriage returns.
strWrap :: String -> Widget n Source #
Make a widget from a string, but wrap the words in the input's lines at the available width using the default wrapping settings. The input string should not contain escape sequences or carriage returns.
Unlike str
, this is greedy horizontally.
strWrapWith :: WrapSettings -> String -> Widget n Source #
Make a widget from a string, but wrap the words in the input's lines at the available width using the specified wrapping settings. The input string should not contain escape sequences or carriage returns.
Unlike str
, this is greedy horizontally.
fill :: Char -> Widget n Source #
Fill all available space with the specified character. Grows both horizontally and vertically.
hyperlink :: Text -> Widget n -> Widget n Source #
Hyperlink the given widget to the specified URL. Not all terminal emulators support this. In those that don't, this should have no discernible effect.
Padding
The type of padding.
padLeft :: Padding -> Widget n -> Widget n Source #
Pad the specified widget on the left. If max padding is used, this grows greedily horizontally; otherwise it defers to the padded widget.
padRight :: Padding -> Widget n -> Widget n Source #
Pad the specified widget on the right. If max padding is used, this grows greedily horizontally; otherwise it defers to the padded widget.
padTop :: Padding -> Widget n -> Widget n Source #
Pad the specified widget on the top. If max padding is used, this grows greedily vertically; otherwise it defers to the padded widget.
padBottom :: Padding -> Widget n -> Widget n Source #
Pad the specified widget on the bottom. If max padding is used, this grows greedily vertically; otherwise it defers to the padded widget.
padLeftRight :: Int -> Widget n -> Widget n Source #
Pad a widget on the left and right. Defers to the padded widget for growth policy.
padTopBottom :: Int -> Widget n -> Widget n Source #
Pad a widget on the top and bottom. Defers to the padded widget for growth policy.
padAll :: Int -> Widget n -> Widget n Source #
Pad a widget on all sides. Defers to the padded widget for growth policy.
Box layout
Vertical box layout: put the specified widgets one above the other
in the specified order. Defers growth policies to the growth policies
of both widgets. This operator is a binary version of vBox
.
Horizontal box layout: put the specified widgets next to each other
in the specified order. Defers growth policies to the growth policies
of both widgets. This operator is a binary version of hBox
.
hBox :: [Widget n] -> Widget n Source #
Horizontal box layout: put the specified widgets next to each other in the specified order (leftmost first). Defers growth policies to the growth policies of the contained widgets (if any are greedy, so is the box).
Allocates space to Fixed
elements first and Greedy
elements
second. For example, if an hBox
contains three elements A
, B
,
and C
, and if A
and B
are Fixed
, then hBox
first renders
A
and B
. Suppose those two take up 10 columns total, and the
hBox
was given 50 columns. This means hBox
then allocates the
remaining 40 columns to C
. If, on the other hand, A
and B
take
up 50 columns together, C
will not be rendered at all.
If all elements are Greedy
, hBox
allocates the available width
evenly among the elements. So, for example, if an hBox
is rendered
in 90 columns and has three Greedy
elements, each element will be
allocated 30 columns.
vBox :: [Widget n] -> Widget n Source #
Vertical box layout: put the specified widgets one above the other in the specified order (uppermost first). Defers growth policies to the growth policies of the contained widgets (if any are greedy, so is the box).
Allocates space to Fixed
elements first and Greedy
elements
second. For example, if a vBox
contains three elements A
, B
,
and C
, and if A
and B
are Fixed
, then vBox
first renders
A
and B
. Suppose those two take up 10 rows total, and the vBox
was given 50 rows. This means vBox
then allocates the remaining
40 rows to C
. If, on the other hand, A
and B
take up 50 rows
together, C
will not be rendered at all.
If all elements are Greedy
, vBox
allocates the available height
evenly among the elements. So, for example, if a vBox
is rendered
in 90 rows and has three Greedy
elements, each element will be
allocated 30 rows.
Limits
hLimit :: Int -> Widget n -> Widget n Source #
Limit the space available to the specified widget to the specified number of columns. This is important for constraining the horizontal growth of otherwise-greedy widgets. This is non-greedy horizontally and defers to the limited widget vertically.
hLimitPercent :: Int -> Widget n -> Widget n Source #
Limit the space available to the specified widget to the specified percentage of available width, as a value between 0 and 100 inclusive. Values outside the valid range will be clamped to the range endpoints. This is important for constraining the horizontal growth of otherwise-greedy widgets. This is non-greedy horizontally and defers to the limited widget vertically.
vLimit :: Int -> Widget n -> Widget n Source #
Limit the space available to the specified widget to the specified number of rows. This is important for constraining the vertical growth of otherwise-greedy widgets. This is non-greedy vertically and defers to the limited widget horizontally.
vLimitPercent :: Int -> Widget n -> Widget n Source #
Limit the space available to the specified widget to the specified percentage of available height, as a value between 0 and 100 inclusive. Values outside the valid range will be clamped to the range endpoints. This is important for constraining the vertical growth of otherwise-greedy widgets. This is non-greedy vertically and defers to the limited widget horizontally.
setAvailableSize :: (Int, Int) -> Widget n -> Widget n Source #
Set the rendering context height and width for this widget. This is useful for relaxing the rendering size constraints on e.g. layer widgets where cropping to the screen size is undesirable.
Attribute management
withDefAttr :: AttrName -> Widget n -> Widget n Source #
Update the attribute map used while rendering the specified widget (and any sub-widgets): set its new *default* attribute (i.e. the attribute components that will be applied if not overridden by any more specific attributes) to the one that we get by looking up the specified attribute name in the map.
For example:
... appAttrMap = attrMap (whiteon
blue) [ ("highlight", fg yellow) , ("warning", bg magenta) , ("good", whiteon
green) ] ... renderA :: (String, String) -> [Widget n] renderA (a,b) = hBox [ withAttr "good" (str a) , str " is " , withAttr "highlight" (str b) ] render1 = renderA ("Brick", "fun") render2 = withDefAttr "warning" render1
In the above, render1 will show "Brick is fun" where the first word is white on a green background, the middle word is white on a blue background, and the last word is yellow on a blue background. However, render2 will show the first word in the same colors but the middle word will be shown in whatever the terminal's normal foreground is on a magenta background, and the third word will be yellow on a magenta background.
modifyDefAttr :: (Attr -> Attr) -> Widget n -> Widget n Source #
Update the attribute map while rendering the specified widget: set
the map's default attribute to the one that we get by applying the
specified function to the current map's default attribute. This is a
variant of withDefAttr
; see the latter for more information.
withAttr :: AttrName -> Widget n -> Widget n Source #
When drawing the specified widget, set the attribute used for
drawing to the one with the specified name. Note that the widget may
make further changes to the active drawing attribute, so this only
takes effect if nothing in the specified widget invokes withAttr
or otherwise changes the rendering context's attribute setup. If you
want to prevent that, use forceAttr
. Attributes used this way still
get merged hierarchically and still fall back to the attribute map's
default attribute. If you want to change the default attribute, use
withDefAttr
.
For example:
appAttrMap = attrMap (white on
blue) [ ("highlight", fg yellow)
, ("warning", bg magenta)
]
renderA :: (String, String) -> [Widget n]
renderA (a,b) = hBox [ str a
, str " is "
, withAttr "highlight" (str b)
]
render1 = renderA ("Brick", "fun")
render2 = withAttr "warning" render1
In the example above, render1
will show Brick is fun
where the
first two words are white on a blue background and the last word
is yellow on a blue background. However, render2
will show the
first two words in white on magenta although the last word is still
rendered in yellow on blue.
forceAttr :: AttrName -> Widget n -> Widget n Source #
When rendering the specified widget, force all attribute lookups
in the attribute map to use the value currently assigned to the
specified attribute name. This means that the attribute lookups will
behave as if they all used the name specified here. That further
means that the resolved attribute will still inherit from its parent
entry in the attribute map as would normally be the case. If you
want to have more control over the resulting attribute, consider
modifyDefAttr
.
For example:
...
appAttrMap = attrMap (white on
blue) [ ("highlight", fg yellow)
, ("notice", fg red) ]
...
renderA :: (String, String) -> [Widget n]
renderA (a,b) = hBox [ withAttr "highlight" (str a)
, str " is "
, withAttr "highlight" (str b)
]
render1 = renderA (Brick, "fun")
render2 = forceAttr "notice" render1
In the above, render1 will show "Brick is fun" where the first and last words are yellow on a blue background and the middle word is white on a blue background. However, render2 will show all words in red on a blue background. In both versions, the middle word will be in white on a blue background.
overrideAttr :: AttrName -> AttrName -> Widget n -> Widget n Source #
Override the lookup of the attribute name targetName
to return
the attribute value associated with fromName
when rendering the
specified widget.
For example:
appAttrMap = attrMap (white on
blue) [ ("highlight", fg yellow)
, ("notice", fg red)
]
renderA :: (String, String) -> [Widget n]
renderA (a, b) = str a + str " is " + withAttr "highlight" (str b)
render1 = withAttr "notice" $ renderA (Brick, "fun")
render2 = overrideAttr "highlight" "notice" render1
In the example above, render1
will show Brick is fun
where the
first two words are red on a blue background, but fun
is yellow on
a blue background. However, render2
will show all three words in
red on a blue background.
updateAttrMap :: (AttrMap -> AttrMap) -> Widget n -> Widget n Source #
While rendering the specified widget, use a transformed version
of the current attribute map. This is a very general function with
broad capabilities: you probably want a more specific function such
as withDefAttr
or withAttr
.
Border style management
withBorderStyle :: BorderStyle -> Widget n -> Widget n Source #
When rendering the specified widget, use the specified border style for any border rendering.
joinBorders :: Widget n -> Widget n Source #
When rendering the specified widget, create borders that respond dynamically to their neighbors to form seamless connections.
separateBorders :: Widget n -> Widget n Source #
When rendering the specified widget, use static borders. This may be marginally faster, but will introduce a small gap between neighboring orthogonal borders.
This is the default for backwards compatibility.
freezeBorders :: Widget n -> Widget n Source #
After the specified widget has been rendered, freeze its borders. A
frozen border will not be affected by neighbors, nor will it affect
neighbors. Compared to separateBorders
, freezeBorders
will not
affect whether borders connect internally to a widget (whereas
separateBorders
prevents them from connecting).
Frozen borders cannot be thawed.
Cursor placement
showCursor :: n -> Location -> Widget n -> Widget n Source #
When rendering the specified widget, also register a cursor positioning request using the specified name and location.
putCursor :: n -> Location -> Widget n -> Widget n Source #
When rendering the specified widget, also register a cursor positioning request using the specified name and location. The cursor will only be positioned but not made visible.
Naming
class Named a n where Source #
The class of types that store interface element names.
Instances
Named (FileBrowser n) n Source # | |
Defined in Brick.Widgets.FileBrowser getName :: FileBrowser n -> n Source # | |
Named (Editor t n) n Source # | |
Defined in Brick.Widgets.Edit | |
Named (GenericList n t e) n Source # | |
Defined in Brick.Widgets.List getName :: GenericList n t e -> n Source # |
Translation and positioning
translateBy :: Location -> Widget n -> Widget n Source #
Translate the specified widget by the specified offset amount. Defers to the translated widget for growth policy.
relativeTo :: Ord n => n -> Location -> Widget n -> Widget n Source #
Given a widget, translate it to position it relative to the upper-left coordinates of a reported extent with the specified positioning offset. If the specified name has no reported extent, this just draws the specified widget with no special positioning.
This is only useful for positioning something in a higher layer
relative to a reported extent in a lower layer. Any other use is
likely to result in the specified widget being rendered as-is with
no translation. This is because this function relies on information
about lower layer renderings in order to work; using it with a
resource name that wasn't rendered in a lower layer will result in
this being equivalent to id
.
For example, if you have two layers topLayer
and bottomLayer
,
then a widget drawn in bottomLayer
with reportExtent Foo
can be
used to relatively position a widget in topLayer
with topLayer =
relativeTo Foo ...
.
Cropping
cropLeftBy :: Int -> Widget n -> Widget n Source #
Crop the specified widget on the left by the specified number of columns. Defers to the cropped widget for growth policy.
cropRightBy :: Int -> Widget n -> Widget n Source #
Crop the specified widget on the right by the specified number of columns. Defers to the cropped widget for growth policy.
cropTopBy :: Int -> Widget n -> Widget n Source #
Crop the specified widget on the top by the specified number of rows. Defers to the cropped widget for growth policy.
cropBottomBy :: Int -> Widget n -> Widget n Source #
Crop the specified widget on the bottom by the specified number of rows. Defers to the cropped widget for growth policy.
cropLeftTo :: Int -> Widget n -> Widget n Source #
Crop the specified widget to the specified size from the left. Defers to the cropped widget for growth policy.
cropRightTo :: Int -> Widget n -> Widget n Source #
Crop the specified widget to the specified size from the right. Defers to the cropped widget for growth policy.
cropTopTo :: Int -> Widget n -> Widget n Source #
Crop the specified widget to the specified size from the top. Defers to the cropped widget for growth policy.
cropBottomTo :: Int -> Widget n -> Widget n Source #
Crop the specified widget to the specified size from the bottom. Defers to the cropped widget for growth policy.
Extent reporting
reportExtent :: Ord n => n -> Widget n -> Widget n Source #
Render the specified widget and record its rendering extent using
the specified name (see also lookupExtent
).
This function is the counterpart to makeVisible
; any visibility
requests made with makeVisible
must have a corresponding
reportExtent
in order to work. The clickable
function will also
work for this purpose to tell the renderer about the clickable
region.
clickable :: Ord n => n -> Widget n -> Widget n Source #
Request mouse click events on the specified widget.
Regions used with clickable
can be scrolled into view with
makeVisible
.
Scrollable viewports
:: (Ord n, Show n) | |
=> n | The name of the viewport (must be unique and stable for reliable behavior) |
-> ViewportType | The type of viewport (indicates the permitted scrolling direction) |
-> Widget n | The widget to be rendered in the scrollable viewport |
-> Widget n |
Render the specified widget in a named viewport with the
specified type. This permits widgets to be scrolled without being
scrolling-aware. To make the most use of viewports, the specified
widget should use the visible
combinator to make a "visibility
request". This viewport combinator will then translate the resulting
rendering to make the requested region visible. In addition, the
EventM
monad provides primitives to scroll viewports
created by this function if visible
is not what you want.
This function can automatically render vertical and horizontal scroll
bars if desired. To enable scroll bars, wrap your call to viewport
with a call to withVScrollBars
and/or withHScrollBars
. If you
don't like the appearance of the resulting scroll bars (defaults:
verticalScrollbarRenderer
and horizontalScrollbarRenderer
),
you can customize how they are drawn by making your own
VScrollbarRenderer
or HScrollbarRenderer
and using
withVScrollBarRenderer
and/or withHScrollBarRenderer
. Note that
when you enable scrollbars, the content of your viewport will lose
one column of available space if vertical scroll bars are enabled and
one row of available space if horizontal scroll bars are enabled.
If a viewport receives more than one visibility request, then the
visibility requests are merged with the inner visibility request
taking preference. If a viewport receives more than one scrolling
request from EventM
, all are honored in the order in
which they are received.
Some caution should be advised when using this function. The viewport renders its contents anew each time the viewport is drawn; in many cases this is prohibitively expensive, and viewports should not be used to display large contents for scrolling. This function is best used when the contents are not too large OR when the contents are large and render-cacheable.
Also, be aware that there is a rich API for accessing viewport
information from within the EventM
monad; check the docs for
Brick.Main
to learn more about ways to get information about
viewports after they're drawn.
visible :: Widget n -> Widget n Source #
Request that the specified widget be made visible when it is
rendered inside a viewport. This permits widgets (whose sizes and
positions cannot be known due to being embedded in arbitrary layouts)
to make a request for a parent viewport to locate them and scroll
enough to put them in view. This, together with viewport
, is what
makes the text editor and list widgets possible without making them
deal with the details of scrolling state management.
This does nothing if not rendered in a viewport.
visibleRegion :: Location -> DisplayRegion -> Widget n -> Widget n Source #
Similar to visible
, request that a region (with the specified
Location
as its origin and DisplayRegion
as its size) be made
visible when it is rendered inside a viewport. The Location
is
relative to the specified widget's upper-left corner of (0, 0).
This does nothing if not rendered in a viewport.
unsafeLookupViewport :: Ord n => n -> RenderM n (Maybe Viewport) Source #
Given a name, obtain the viewport for that name by consulting the viewport map in the rendering monad. NOTE! Some care must be taken when calling this function, since it only returns useful values after the viewport in question has been rendered. If you call this function during rendering before a viewport has been rendered, you may get nothing or you may get a stale version of the viewport. This is because viewports are updated during rendering and the one you are interested in may not have been rendered yet. So if you want to use this, be sure you know what you are doing.
cached :: Ord n => n -> Widget n -> Widget n Source #
If the specified resource name has an entry in the rendering cache, use the rendered version from the cache. If not, render the specified widget and update the cache with the result.
To ensure that mouse events are emitted correctly for cached widgets, in addition to the rendered widget, we also cache (the names of) any clickable extents that were rendered and restore that when utilizing the cache.
See also invalidateCacheEntry
.
Viewport scroll bars
withVScrollBars :: VScrollBarOrientation -> Widget n -> Widget n Source #
Enable vertical scroll bars on all viewports in the specified widget and draw them with the specified orientation.
withHScrollBars :: HScrollBarOrientation -> Widget n -> Widget n Source #
Enable horizontal scroll bars on all viewports in the specified widget and draw them with the specified orientation.
withClickableHScrollBars :: (ClickableScrollbarElement -> n -> n) -> Widget n -> Widget n Source #
Enable mouse click reporting on horizontal scroll bars in the
specified widget. This must be used with withHScrollBars
. The
provided function is used to build a resource name containing the
scroll bar element clicked and the viewport name associated with the
scroll bar. It is usually a data constructor of the n
type.
withClickableVScrollBars :: (ClickableScrollbarElement -> n -> n) -> Widget n -> Widget n Source #
Enable mouse click reporting on vertical scroll bars in the
specified widget. This must be used with withVScrollBars
. The
provided function is used to build a resource name containing the
scroll bar element clicked and the viewport name associated with the
scroll bar. It is usually a data constructor of the n
type.
withVScrollBarHandles :: Widget n -> Widget n Source #
Enable scroll bar handles on all vertical scroll bars in the
specified widget. Handles appear at the ends of the scroll bar,
representing the "handles" that are typically clickable in
graphical UIs to move the scroll bar incrementally. Vertical
scroll bars are also clickable if mouse mode is enabled and if
withClickableVScrollBars
is used.
This will only have an effect if withVScrollBars
is also called.
withHScrollBarHandles :: Widget n -> Widget n Source #
Enable scroll bar handles on all horizontal scroll bars in
the specified widget. Handles appear at the ends of the scroll
bar, representing the "handles" that are typically clickable in
graphical UIs to move the scroll bar incrementally. Horizontal
scroll bars are also clickable if mouse mode is enabled and if
withClickableHScrollBars
is used.
This will only have an effect if withHScrollBars
is also called.
withVScrollBarRenderer :: VScrollbarRenderer n -> Widget n -> Widget n Source #
Render vertical viewport scroll bars in the specified widget with
the specified renderer. This is only needed if you want to override
the use of the default renderer, verticalScrollbarRenderer
.
withHScrollBarRenderer :: HScrollbarRenderer n -> Widget n -> Widget n Source #
Render horizontal viewport scroll bars in the specified widget with
the specified renderer. This is only needed if you want to override
the use of the default renderer, horizontalScrollbarRenderer
.
data VScrollbarRenderer n Source #
A vertical scroll bar renderer.
VScrollbarRenderer | |
|
data HScrollbarRenderer n Source #
A horizontal scroll bar renderer.
HScrollbarRenderer | |
|
verticalScrollbarRenderer :: VScrollbarRenderer n Source #
The default renderer for vertical viewport scroll bars. Override
with withVScrollBarRenderer
.
horizontalScrollbarRenderer :: HScrollbarRenderer n Source #
The default renderer for horizontal viewport scroll bars. Override
with withHScrollBarRenderer
.
scrollbarAttr :: AttrName Source #
The base attribute for scroll bars.
scrollbarTroughAttr :: AttrName Source #
The attribute for scroll bar troughs. This attribute is a
specialization of scrollbarAttr
.
scrollbarHandleAttr :: AttrName Source #
The attribute for scroll bar handles. This attribute is a
specialization of scrollbarAttr
.
:: Ord n | |
=> VScrollbarRenderer n | The renderer to use. |
-> VScrollBarOrientation | The scroll bar orientation. The orientation
governs how additional padding is added to
the scroll bar if it is smaller than it space
allocation according to |
-> n | The viewport name associated with this scroll bar. |
-> Maybe (ClickableScrollbarElement -> n -> n) | Constructor for clickable scroll bar element names. |
-> Bool | Whether to display handles. |
-> Int | The total viewport height in effect. |
-> Int | The viewport vertical scrolling offset in effect. |
-> Int | The total viewport content height. |
-> Widget n |
Build a vertical scroll bar using the specified renderer and settings.
You probably don't want to use this directly; instead,
use viewport
, withVScrollBars
, and, if needed,
withVScrollBarRenderer
. This is exposed so that if you want to
render a scroll bar of your own, you can do so outside the viewport
context.
:: Ord n | |
=> HScrollbarRenderer n | The renderer to use. |
-> HScrollBarOrientation | The scroll bar orientation. The orientation
governs how additional padding is added
to the scroll bar if it is smaller
than it space allocation according to
|
-> n | The viewport name associated with this scroll bar. |
-> Maybe (ClickableScrollbarElement -> n -> n) | Constructor for clickable scroll bar element names. Will be given the element name and the viewport name. |
-> Bool | Whether to show handles. |
-> Int | The total viewport width in effect. |
-> Int | The viewport horizontal scrolling offset in effect. |
-> Int | The total viewport content width. |
-> Widget n |
Build a horizontal scroll bar using the specified renderer and settings.
You probably don't want to use this directly; instead, use
viewport
, withHScrollBars
, and, if needed,
withHScrollBarRenderer
. This is exposed so that if you want to
render a scroll bar of your own, you can do so outside the viewport
context.
Adding offsets to cursor positions and visibility requests
addResultOffset :: Location -> Result n -> Result n Source #
Add an offset to all cursor locations, visibility requests, and extents in the specified rendering result. This function is critical for maintaining correctness in the rendering results as they are processed successively by box layouts and other wrapping combinators, since calls to this function result in converting from widget-local coordinates to (ultimately) terminal-global ones so they can be used by other combinators. You should call this any time you render something and then translate it or otherwise offset it from its original origin.
Cropping results
cropToContext :: Widget n -> Widget n Source #
After rendering the specified widget, crop its result image to the dimensions in the rendering context.