Move Padding type from Brick.Types to Brick.Widgets.Core

This commit is contained in:
Jonathan Daugherty 2022-07-22 16:07:00 -07:00
parent f2b2586d53
commit bf2f6be870
8 changed files with 18 additions and 15 deletions

View File

@ -17,7 +17,8 @@ import Brick.Types
, BrickEvent(..)
)
import Brick.Widgets.Core
( vBox
( Padding(..)
, vBox
, padTopBottom
, withDefAttr
, cached
@ -51,7 +52,7 @@ drawUi i = [ui]
, padTopBottom 1 $
cached ExpensiveWidget $
withDefAttr emphAttr $ str $ "This widget is cached (state = " <> show i <> ")"
, padBottom (T.Pad 1) $
, padBottom (Pad 1) $
withDefAttr emphAttr $ str $ "This widget is not cached (state = " <> show i <> ")"
, hCenter $ str "Press 'i' to invalidate the cache,"
, str "'+' to change the state value, and"

View File

@ -4,7 +4,6 @@ module Main where
import Brick.Main (App(..), neverShowCursor, resizeOrQuit, defaultMain)
import Brick.Types
( Widget
, Padding(..)
)
import Brick.Widgets.Core
( vBox
@ -20,6 +19,7 @@ import Brick.Widgets.Core
, cropRightTo
, cropTopTo
, cropBottomTo
, Padding(..)
)
import Brick.Widgets.Border (border)
import Brick.AttrMap (attrMap)

View File

@ -28,6 +28,7 @@ import Brick.Widgets.Core
( vBox, (<=>), padTop
, hLimit, vLimit, txt
, withDefAttr, emptyWidget
, Padding(..)
)
import qualified Brick.Widgets.FileBrowser as FB
import qualified Brick.AttrMap as A
@ -45,7 +46,7 @@ drawUI b = [center $ ui <=> help]
hLimit 50 $
borderWithLabel (txt "Choose a file") $
FB.renderFileBrowser True b
help = padTop (T.Pad 1) $
help = padTop (Pad 1) $
vBox [ case FB.fileBrowserException b of
Nothing -> emptyWidget
Just e -> hCenter $ withDefAttr errorAttr $

View File

@ -45,7 +45,7 @@ drawUi st =
buttonLayer :: St -> Widget Name
buttonLayer st =
C.vCenterLayer $
C.hCenterLayer (padBottom (T.Pad 1) $ str "Click a button:") <=>
C.hCenterLayer (padBottom (Pad 1) $ str "Click a button:") <=>
C.hCenterLayer (hBox $ padLeftRight 1 <$> buttons) <=>
C.hCenterLayer (padTopBottom 1 $ str "Or enter text and then click in this editor:") <=>
C.hCenterLayer (vLimit 3 $ hLimit 50 $ E.renderEditor (str . unlines) True (st^.edit))

View File

@ -4,7 +4,6 @@ module Main where
import Brick.Main (App(..), neverShowCursor, resizeOrQuit, defaultMain)
import Brick.Types
( Widget
, Padding(..)
)
import Brick.Widgets.Core
( vBox
@ -17,6 +16,7 @@ import Brick.Widgets.Core
, padBottom
, padTopBottom
, padLeftRight
, Padding(..)
)
import qualified Brick.Widgets.Border as B
import qualified Brick.Widgets.Center as C

View File

@ -29,7 +29,8 @@ import Brick.AttrMap
, attrMap
)
import Brick.Widgets.Core
( hLimit
( Padding(..)
, hLimit
, vLimit
, padRight
, hBox
@ -72,7 +73,7 @@ drawUi st = [ui]
, C.hCenter (str "Last clicked scroll bar element:")
, str $ show $ _lastClickedElement st
])
pair = hBox [ padRight (T.Pad 5) $
pair = hBox [ padRight (Pad 5) $
B.border $
withClickableHScrollBars SBClick $
withHScrollBars OnBottom $

View File

@ -84,7 +84,6 @@ module Brick.Types
-- * Miscellaneous
, Size(..)
, Padding(..)
, Direction(..)
-- * Renderer internals (for benchmarking)
@ -113,12 +112,6 @@ import Brick.Types.Internal
import Brick.Types.EventM
import Brick.AttrMap (AttrName, attrMapLookup)
-- | The type of padding.
data Padding = Pad Int
-- ^ Pad by the specified number of rows or columns.
| Max
-- ^ Pad up to the number of available rows or columns.
-- | Given a state value and an 'EventM' that mutates that state, run
-- the specified action and return both the resulting modified state and
-- the result of the action itself.

View File

@ -22,6 +22,7 @@ module Brick.Widgets.Core
, hyperlink
-- * Padding
, Padding(..)
, padLeft
, padRight
, padTop
@ -375,6 +376,12 @@ hyperlink url p =
let attr = (c^.attrL) `V.withURL` url
withReaderT (ctxAttrMapL %~ setDefaultAttr attr) (render p)
-- | The type of padding.
data Padding = Pad Int
-- ^ Pad by the specified number of rows or columns.
| Max
-- ^ Pad up to the number of available rows or columns.
-- | Pad the specified widget on the left. If max padding is used, this
-- grows greedily horizontally; otherwise it defers to the padded
-- widget.