{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
module Brick.Widgets.Border.Style
( BorderStyle(..)
, borderStyleFromChar
, ascii
, unicode
, unicodeBold
, unicodeRounded
, defaultBorderStyle
)
where
import GHC.Generics
import Control.DeepSeq
data BorderStyle =
BorderStyle { BorderStyle -> Char
bsCornerTL :: Char
, BorderStyle -> Char
bsCornerTR :: Char
, BorderStyle -> Char
bsCornerBR :: Char
, BorderStyle -> Char
bsCornerBL :: Char
, BorderStyle -> Char
bsIntersectFull :: Char
, BorderStyle -> Char
bsIntersectL :: Char
, BorderStyle -> Char
bsIntersectR :: Char
, BorderStyle -> Char
bsIntersectT :: Char
, BorderStyle -> Char
bsIntersectB :: Char
, BorderStyle -> Char
bsHorizontal :: Char
, BorderStyle -> Char
bsVertical :: Char
}
deriving (Int -> BorderStyle -> ShowS
[BorderStyle] -> ShowS
BorderStyle -> String
(Int -> BorderStyle -> ShowS)
-> (BorderStyle -> String)
-> ([BorderStyle] -> ShowS)
-> Show BorderStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BorderStyle -> ShowS
showsPrec :: Int -> BorderStyle -> ShowS
$cshow :: BorderStyle -> String
show :: BorderStyle -> String
$cshowList :: [BorderStyle] -> ShowS
showList :: [BorderStyle] -> ShowS
Show, ReadPrec [BorderStyle]
ReadPrec BorderStyle
Int -> ReadS BorderStyle
ReadS [BorderStyle]
(Int -> ReadS BorderStyle)
-> ReadS [BorderStyle]
-> ReadPrec BorderStyle
-> ReadPrec [BorderStyle]
-> Read BorderStyle
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS BorderStyle
readsPrec :: Int -> ReadS BorderStyle
$creadList :: ReadS [BorderStyle]
readList :: ReadS [BorderStyle]
$creadPrec :: ReadPrec BorderStyle
readPrec :: ReadPrec BorderStyle
$creadListPrec :: ReadPrec [BorderStyle]
readListPrec :: ReadPrec [BorderStyle]
Read, BorderStyle -> BorderStyle -> Bool
(BorderStyle -> BorderStyle -> Bool)
-> (BorderStyle -> BorderStyle -> Bool) -> Eq BorderStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BorderStyle -> BorderStyle -> Bool
== :: BorderStyle -> BorderStyle -> Bool
$c/= :: BorderStyle -> BorderStyle -> Bool
/= :: BorderStyle -> BorderStyle -> Bool
Eq, (forall x. BorderStyle -> Rep BorderStyle x)
-> (forall x. Rep BorderStyle x -> BorderStyle)
-> Generic BorderStyle
forall x. Rep BorderStyle x -> BorderStyle
forall x. BorderStyle -> Rep BorderStyle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BorderStyle -> Rep BorderStyle x
from :: forall x. BorderStyle -> Rep BorderStyle x
$cto :: forall x. Rep BorderStyle x -> BorderStyle
to :: forall x. Rep BorderStyle x -> BorderStyle
Generic, BorderStyle -> ()
(BorderStyle -> ()) -> NFData BorderStyle
forall a. (a -> ()) -> NFData a
$crnf :: BorderStyle -> ()
rnf :: BorderStyle -> ()
NFData)
defaultBorderStyle :: BorderStyle
defaultBorderStyle :: BorderStyle
defaultBorderStyle = BorderStyle
unicode
borderStyleFromChar :: Char -> BorderStyle
borderStyleFromChar :: Char -> BorderStyle
borderStyleFromChar Char
c =
Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> BorderStyle
BorderStyle Char
c Char
c Char
c Char
c Char
c Char
c Char
c Char
c Char
c Char
c Char
c
ascii :: BorderStyle
ascii :: BorderStyle
ascii =
BorderStyle { bsCornerTL :: Char
bsCornerTL = Char
'+'
, bsCornerTR :: Char
bsCornerTR = Char
'+'
, bsCornerBR :: Char
bsCornerBR = Char
'+'
, bsCornerBL :: Char
bsCornerBL = Char
'+'
, bsIntersectFull :: Char
bsIntersectFull = Char
'+'
, bsIntersectL :: Char
bsIntersectL = Char
'+'
, bsIntersectR :: Char
bsIntersectR = Char
'+'
, bsIntersectT :: Char
bsIntersectT = Char
'+'
, bsIntersectB :: Char
bsIntersectB = Char
'+'
, bsHorizontal :: Char
bsHorizontal = Char
'-'
, bsVertical :: Char
bsVertical = Char
'|'
}
unicode :: BorderStyle
unicode :: BorderStyle
unicode =
BorderStyle { bsCornerTL :: Char
bsCornerTL = Char
'┌'
, bsCornerTR :: Char
bsCornerTR = Char
'┐'
, bsCornerBR :: Char
bsCornerBR = Char
'┘'
, bsCornerBL :: Char
bsCornerBL = Char
'└'
, bsIntersectFull :: Char
bsIntersectFull = Char
'┼'
, bsIntersectL :: Char
bsIntersectL = Char
'├'
, bsIntersectR :: Char
bsIntersectR = Char
'┤'
, bsIntersectT :: Char
bsIntersectT = Char
'┬'
, bsIntersectB :: Char
bsIntersectB = Char
'┴'
, bsHorizontal :: Char
bsHorizontal = Char
'─'
, bsVertical :: Char
bsVertical = Char
'│'
}
unicodeBold :: BorderStyle
unicodeBold :: BorderStyle
unicodeBold =
BorderStyle { bsCornerTL :: Char
bsCornerTL = Char
'┏'
, bsCornerTR :: Char
bsCornerTR = Char
'┓'
, bsCornerBR :: Char
bsCornerBR = Char
'┛'
, bsCornerBL :: Char
bsCornerBL = Char
'┗'
, bsIntersectFull :: Char
bsIntersectFull = Char
'╋'
, bsIntersectL :: Char
bsIntersectL = Char
'┣'
, bsIntersectR :: Char
bsIntersectR = Char
'┫'
, bsIntersectT :: Char
bsIntersectT = Char
'┳'
, bsIntersectB :: Char
bsIntersectB = Char
'┻'
, bsHorizontal :: Char
bsHorizontal = Char
'━'
, bsVertical :: Char
bsVertical = Char
'┃'
}
unicodeRounded :: BorderStyle
unicodeRounded :: BorderStyle
unicodeRounded =
BorderStyle { bsCornerTL :: Char
bsCornerTL = Char
'╭'
, bsCornerTR :: Char
bsCornerTR = Char
'╮'
, bsCornerBR :: Char
bsCornerBR = Char
'╯'
, bsCornerBL :: Char
bsCornerBL = Char
'╰'
, bsIntersectFull :: Char
bsIntersectFull = Char
'┼'
, bsIntersectL :: Char
bsIntersectL = Char
'├'
, bsIntersectR :: Char
bsIntersectR = Char
'┤'
, bsIntersectT :: Char
bsIntersectT = Char
'┬'
, bsIntersectB :: Char
bsIntersectB = Char
'┴'
, bsHorizontal :: Char
bsHorizontal = Char
'─'
, bsVertical :: Char
bsVertical = Char
'│'
}