Rename multiLine to multiline

This commit is contained in:
Francisco Vallarino 2021-07-31 13:12:52 -03:00
parent 44109ca217
commit da1a9ba726
14 changed files with 38 additions and 38 deletions

View File

@ -449,7 +449,7 @@ buildUI wenv model = traceShow "Creating UI" widgetTree where
label "3",
label "4",
label "5",
label_ "This is a really long label used to check if line breaks and ellipsis are implemented correctly" [multiLine] `styleBasic` [bgColor blue],
label_ "This is a really long label used to check if line breaks and ellipsis are implemented correctly" [multiline] `styleBasic` [bgColor blue],
label "6",
label "This is a really long label used to check if line breaks and ellipsis are implemented correctly, using a longlonglonglonglonglonglonglonglonglonglonglonglonglonglonglong invalid word" `styleBasic` [bgColor blue, textBottom, textRight]
],
@ -509,7 +509,7 @@ buildUI wenv model = traceShow "Creating UI" widgetTree where
] `styleBasic` [bgColor blue]
] `styleBasic` [bgColor green],
hgrid [
label_ "This is a really long label used to check what I did works fine" [multiLine, ellipsis],
label_ "This is a really long label used to check what I did works fine" [multiline, ellipsis],
label "Jj label" `styleHover` [textSize 40]
] `styleHover` [bgColor red],
label (model ^. dropdown1) `styleBasic` [bgColor lightBlue, textLeft],
@ -522,6 +522,6 @@ buildUI wenv model = traceShow "Creating UI" widgetTree where
image_ "https://picsum.photos/1600/400" [fitFill, onLoadError ImageMsg] `styleBasic` [cursorIcon CursorInvalid, border 40 (orange & L.a .~ 0.5), radius 100, radiusBL 0, radiusBR 0]
],
textDropdown_ dropdown1 items id [onChange DropdownVal, onChangeIdx DropdownIdx],
button_ "Click\nme!" (PrintMessage "Button clicked") [] --multiLine, ellipsis
button_ "Click\nme!" (PrintMessage "Button clicked") [] --multiline, ellipsis
] `key` "main vstack" `styleBasic` [borderT 20 red, borderL 10 blue, borderR 10 green, borderB 10 gray, radius 50] --, padding 20
items = fmap (\i -> "This is a long label: " <> showt i) [1..100::Int]

View File

@ -168,13 +168,13 @@ Most widgets support a basic version, such as `label`, and a configurable
version which is denoted by a trailing `_`. In the case of `label_`, some of the
config options are:
- **multiLine**: to split the text into multiple lines if width is not enough.
- **multiline**: to split the text into multiple lines if width is not enough.
- **ellipsis**: to show ellipse when text overflows instead of just cutting it.
For example:
```haskell
label_ "This is\nmultiline text" [multiLine, ellipsis]
label_ "This is\nmultiline text" [multiline, ellipsis]
```
#### Button

View File

@ -60,7 +60,7 @@ bookDetail b = content `styleBasic` [minWidth 500, paddingH 20] where
publishYear = maybe "" showt (b ^. year)
shortLabel value = label value `styleBasic` [textFont "Medium", textTop]
longLabel value = label_ value [multiLine, ellipsis, trimSpaces]
longLabel value = label_ value [multiline, ellipsis, trimSpaces]
content = hstack . concat $ [[
vstack [

View File

@ -123,10 +123,10 @@ class CmbAcceptTab t where
acceptTab_ :: Bool -> t
-- | Whether a text based widget is multiline.
class CmbMultiLine t where
multiLine :: t
multiLine = multiLine_ True
multiLine_ :: Bool -> t
class CmbMultiline t where
multiline :: t
multiline = multiline_ True
multiline_ :: Bool -> t
-- | Whether to use ellipsis or not.
class CmbEllipsis t where

View File

@ -108,7 +108,7 @@ alertMsg_
-> WidgetNode sp ep -- ^ The created dialog.
alertMsg_ message evt configs = newNode where
config = mconcat configs
dialogBody wenv = label_ message [multiLine]
dialogBody wenv = label_ message [multiline]
& L.info . L.style .~ collectTheme wenv L.dialogMsgBodyStyle
createUI = buildUI dialogBody evt config
newNode = compositeD_ "alert" (WidgetValue ()) createUI handleEvent []

View File

@ -132,7 +132,7 @@ confirmMsg_
-> WidgetNode sp ep -- ^ The created dialog.
confirmMsg_ message acceptEvt cancelEvt configs = newNode where
config = mconcat configs
dialogBody wenv = label_ message [multiLine]
dialogBody wenv = label_ message [multiline]
& L.info . L.style .~ collectTheme wenv L.dialogMsgBodyStyle
createUI = buildUI dialogBody acceptEvt cancelEvt config
compCfg = [compositeMergeReqs mergeReqs]

View File

@ -13,7 +13,7 @@ Configs:
- trimSpaces: whether to remove leading/trailing spaces in the caption.
- ellipsis: if ellipsis should be used for overflown text.
- multiLine: if text may be split in multiple lines.
- multiline: if text may be split in multiple lines.
- maxLines: maximum number of text lines to show.
- onFocus: event to raise when focus is received.
- onFocusReq: WidgetRequest to generate when focus is received.
@ -101,9 +101,9 @@ instance CmbEllipsis (ButtonCfg s e) where
_btnLabelCfg = ellipsis_ ellipsis
}
instance CmbMultiLine (ButtonCfg s e) where
multiLine_ multi = def {
_btnLabelCfg = multiLine_ multi
instance CmbMultiline (ButtonCfg s e) where
multiline_ multi = def {
_btnLabelCfg = multiline_ multi
}
instance CmbMaxLines (ButtonCfg s e) where

View File

@ -13,7 +13,7 @@ Configs:
- trimSpaces: whether to remove leading/trailing spaces in the caption.
- ellipsis: if ellipsis should be used for overflown text.
- multiLine: if text may be split in multiple lines.
- multiline: if text may be split in multiple lines.
- maxLines: maximum number of text lines to show.
- onFocus: event to raise when focus is received.
- onFocusReq: WidgetRequest to generate when focus is received.
@ -83,9 +83,9 @@ instance CmbEllipsis (ExternalLinkCfg s e) where
_elcLabelCfg = ellipsis_ ellipsis
}
instance CmbMultiLine (ExternalLinkCfg s e) where
multiLine_ multi = def {
_elcLabelCfg = multiLine_ multi
instance CmbMultiline (ExternalLinkCfg s e) where
multiline_ multi = def {
_elcLabelCfg = multiline_ multi
}
instance CmbMaxLines (ExternalLinkCfg s e) where

View File

@ -12,7 +12,7 @@ Configs:
- trimSpaces: whether to remove leading/trailing spaces in the caption.
- ellipsis: if ellipsis should be used for overflown text.
- multiLine: if text may be split in multiple lines.
- multiline: if text may be split in multiple lines.
- maxLines: maximum number of text lines to show.
- ignoreTheme: whether to load default style from theme or start empty.
- resizeFactor: flexibility to have more or less spaced assigned.
@ -98,8 +98,8 @@ instance CmbEllipsis (LabelCfg s e) where
_lscTextEllipsis = Just ellipsis
}
instance CmbMultiLine (LabelCfg s e) where
multiLine_ multi = def {
instance CmbMultiline (LabelCfg s e) where
multiline_ multi = def {
_lscTextMultiLine = Just multi
}

View File

@ -18,7 +18,7 @@ Configs:
- textBottom: places the label to the bottom of the checkbox.
- trimSpaces: whether to remove leading/trailing spaces in the caption.
- ellipsis: if ellipsis should be used for overflown text.
- multiLine: if text may be split in multiple lines.
- multiline: if text may be split in multiple lines.
- maxLines: maximum number of text lines to show.
- resizeFactor: flexibility to have more or less spaced assigned.
- resizeFactorW: flexibility to have more or less horizontal spaced assigned.
@ -118,9 +118,9 @@ instance CmbEllipsis (LabeledCheckboxCfg s e) where
_lchLabelCfg = ellipsis_ ellipsis
}
instance CmbMultiLine (LabeledCheckboxCfg s e) where
multiLine_ multi = def {
_lchLabelCfg = multiLine_ multi
instance CmbMultiline (LabeledCheckboxCfg s e) where
multiline_ multi = def {
_lchLabelCfg = multiline_ multi
}
instance CmbMaxLines (LabeledCheckboxCfg s e) where

View File

@ -19,7 +19,7 @@ Configs:
- textBottom: places the label to the bottom of the radio.
- trimSpaces: whether to remove leading/trailing spaces in the caption.
- ellipsis: if ellipsis should be used for overflown text.
- multiLine: if text may be split in multiple lines.
- multiline: if text may be split in multiple lines.
- maxLines: maximum number of text lines to show.
- resizeFactor: flexibility to have more or less spaced assigned.
- resizeFactorW: flexibility to have more or less horizontal spaced assigned.
@ -117,9 +117,9 @@ instance CmbEllipsis (LabeledRadioCfg s e a) where
_lchLabelCfg = ellipsis_ ellipsis
}
instance CmbMultiLine (LabeledRadioCfg s e a) where
multiLine_ multi = def {
_lchLabelCfg = multiLine_ multi
instance CmbMultiline (LabeledRadioCfg s e a) where
multiline_ multi = def {
_lchLabelCfg = multiline_ multi
}
instance CmbMaxLines (LabeledRadioCfg s e a) where

View File

@ -866,13 +866,13 @@ replaceSelection textLines currPos currSel addText = result where
(newX, newY, midLines)
| length addLines <= 1 = (T.length (linePre <> addText), selY1, singleLine)
| otherwise = (T.length end, selY1 + length addLines - 1, multiLine)
| otherwise = (T.length end, selY1 + length addLines - 1, multiline)
where
singleLine = Seq.singleton $ linePre <> addText <> lineSuf
begin = Seq.index addLines 0
middle = Seq.drop 1 $ Seq.take (length addLines - 1) addLines
end = Seq.index addLines (length addLines - 1)
multiLine = (linePre <> begin) :<| (middle :|> (end <> lineSuf))
multiline = (linePre <> begin) :<| (middle :|> (end <> lineSuf))
newLines = prevLines <> midLines <> postLines
newText = T.dropEnd 1 $ T.unlines (toList newLines)

View File

@ -90,7 +90,7 @@ getSizeReq = describe "getSizeReq" $ do
wenv = mockWenv ()
btnNode1 = button "Click" BtnClick
btnNode2 = button_ "Click 2" BtnClick [resizeFactorW 1, resizeFactorH 2]
btnNode3 = button_ "Line line line" BtnClick [multiLine, trimSpaces] `styleBasic` [width 50]
btnNode3 = button_ "Line line line" BtnClick [multiline, trimSpaces] `styleBasic` [width 50]
(sizeReqW1, sizeReqH1) = nodeGetSizeReq wenv btnNode1
(sizeReqW2, sizeReqH2) = nodeGetSizeReq wenv btnNode2
(sizeReqW3, sizeReqH3) = nodeGetSizeReq wenv btnNode3

View File

@ -74,7 +74,7 @@ getSizeReqMulti = describe "getSizeReq" $ do
where
wenv = mockWenv ()
lblNode = label_ "Line line line" [multiLine, trimSpaces] `styleBasic` [width 50]
lblNode = label_ "Line line line" [multiline, trimSpaces] `styleBasic` [width 50]
(sizeReqW, sizeReqH) = nodeGetSizeReq wenv lblNode
getSizeReqMultiKeepSpaces :: Spec
@ -88,7 +88,7 @@ getSizeReqMultiKeepSpaces = describe "getSizeReq" $ do
where
wenv = mockWenv ()
caption = "Line line line"
lblNode = label_ caption [multiLine, trimSpaces_ False] `styleBasic` [maxWidth 50]
lblNode = label_ caption [multiline, trimSpaces_ False] `styleBasic` [maxWidth 50]
(sizeReqW, sizeReqH) = nodeGetSizeReq wenv lblNode
getSizeReqMultiMaxLines :: Spec
@ -102,7 +102,7 @@ getSizeReqMultiMaxLines = describe "getSizeReq" $ do
where
wenv = mockWenv ()
caption = "Line line line line line"
lblNode = label_ caption [multiLine, trimSpaces_ False, maxLines 4] `styleBasic` [maxWidth 50]
lblNode = label_ caption [multiline, trimSpaces_ False, maxLines 4] `styleBasic` [maxWidth 50]
(sizeReqW, sizeReqH) = nodeGetSizeReq wenv lblNode
getSizeReqMerge :: Spec
@ -148,6 +148,6 @@ resize = describe "resize" $ do
single = label "Test label"
resSingle = widgetResize (single ^. L.widget) wenv single vp
reqsSingle = resSingle ^. L.requests
multi = label_ "Test label" [multiLine]
multi = label_ "Test label" [multiline]
resMulti = widgetResize (multi ^. L.widget) wenv multi vp
reqsMulti = resMulti ^. L.requests