mirror of
https://github.com/jtdaugherty/brick.git
synced 2025-01-05 21:03:07 +03:00
txt now takes a Text value, str takes a String
This commit is contained in:
parent
aaa3938899
commit
074aff9b3a
@ -23,7 +23,7 @@ import Brick.AttrMap
|
||||
import Brick.Markup
|
||||
import Data.Text.Markup
|
||||
|
||||
styles :: [(String, BorderStyle)]
|
||||
styles :: [(T.Text, BorderStyle)]
|
||||
styles =
|
||||
[ ("ascii", ascii)
|
||||
, ("uni", unicode)
|
||||
@ -122,7 +122,7 @@ listDrawElem :: Bool -> Int -> Render
|
||||
listDrawElem sel i =
|
||||
let selStr s = if sel then "<" <> s <> ">" else s
|
||||
in hCenterWith (Just ' ') $ vBox $ for [1..i+1] $ \j ->
|
||||
(txt $ "Item " <> (selStr $ show i) <> " L" <> show j, High)
|
||||
(str $ "Item " <> (selStr $ show i) <> " L" <> show j, High)
|
||||
|
||||
theAttrMap :: AttrMap
|
||||
theAttrMap = attrMap defAttr
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Main where
|
||||
|
||||
import Graphics.Vty
|
||||
|
@ -19,6 +19,7 @@ module Brick.Border
|
||||
where
|
||||
|
||||
import Data.Monoid ((<>))
|
||||
import qualified Data.Text as T
|
||||
|
||||
import Brick.Render
|
||||
import Brick.AttrMap
|
||||
@ -52,18 +53,18 @@ brCornerAttr = borderAttr <> "corner" <> "br"
|
||||
border :: Render -> Render
|
||||
border = border_ Nothing
|
||||
|
||||
borderWithLabel :: String -> Render -> Render
|
||||
borderWithLabel :: T.Text -> Render -> Render
|
||||
borderWithLabel label = border_ (Just label)
|
||||
|
||||
border_ :: Maybe String -> Render -> Render
|
||||
border_ :: Maybe T.Text -> Render -> Render
|
||||
border_ label wrapped = do
|
||||
bs <- getActiveBorderStyle
|
||||
let top = (withAttrName tlCornerAttr $ txt [bsCornerTL bs])
|
||||
let top = (withAttrName tlCornerAttr $ str [bsCornerTL bs])
|
||||
<<+ hBorder_ label +>>
|
||||
(withAttrName trCornerAttr $ txt [bsCornerTR bs])
|
||||
bottom = (withAttrName blCornerAttr $ txt [bsCornerBL bs])
|
||||
(withAttrName trCornerAttr $ str [bsCornerTR bs])
|
||||
bottom = (withAttrName blCornerAttr $ str [bsCornerBL bs])
|
||||
<<+ hBorder +>>
|
||||
(withAttrName brCornerAttr $ txt [bsCornerBR bs])
|
||||
(withAttrName brCornerAttr $ str [bsCornerBR bs])
|
||||
middle = vBorder +>> wrapped <<+ vBorder
|
||||
total = top =>> middle <<= bottom
|
||||
total
|
||||
@ -71,10 +72,10 @@ border_ label wrapped = do
|
||||
hBorder :: Render
|
||||
hBorder = hBorder_ Nothing
|
||||
|
||||
hBorderWithLabel :: String -> Render
|
||||
hBorderWithLabel :: T.Text -> Render
|
||||
hBorderWithLabel label = hBorder_ (Just label)
|
||||
|
||||
hBorder_ :: Maybe String -> Render
|
||||
hBorder_ :: Maybe T.Text -> Render
|
||||
hBorder_ label = do
|
||||
bs <- getActiveBorderStyle
|
||||
withAttrName hBorderAttr $ hCenterWith (Just $ bsHorizontal bs) msg
|
||||
|
@ -22,6 +22,7 @@ module Brick.Render
|
||||
, Direction(..)
|
||||
|
||||
, txt
|
||||
, str
|
||||
, hPad
|
||||
, vPad
|
||||
, hFill
|
||||
|
@ -32,6 +32,7 @@ module Brick.Render.Internal
|
||||
, ViewportType(..)
|
||||
|
||||
, txt
|
||||
, str
|
||||
, hPad
|
||||
, vPad
|
||||
, hFill
|
||||
@ -67,6 +68,7 @@ import Control.Monad (when)
|
||||
import Control.Monad.Trans.State.Lazy
|
||||
import Control.Monad.Trans.Reader
|
||||
import Control.Monad.Trans.Class (lift)
|
||||
import qualified Data.Text as T
|
||||
import Data.Default
|
||||
import Data.Functor.Contravariant
|
||||
import Data.Monoid ((<>), mempty)
|
||||
@ -138,7 +140,7 @@ makeLenses ''Viewport
|
||||
makeLenses ''RenderState
|
||||
|
||||
instance IsString Render where
|
||||
fromString = txt
|
||||
fromString = str
|
||||
|
||||
instance Default Result where
|
||||
def = Result V.emptyImage [] []
|
||||
@ -186,11 +188,14 @@ lookupAttrName n = do
|
||||
c <- getContext
|
||||
return $ attrMapLookup n (c^.ctxAttrs)
|
||||
|
||||
txt :: String -> Render
|
||||
txt s = do
|
||||
str :: String -> Render
|
||||
str s = do
|
||||
c <- getContext
|
||||
return $ def & image .~ (V.string (c^.attr) s)
|
||||
|
||||
txt :: T.Text -> Render
|
||||
txt = str . T.unpack
|
||||
|
||||
hPad :: Char -> Render
|
||||
hPad ch = do
|
||||
c <- getContext
|
||||
|
Loading…
Reference in New Issue
Block a user