{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
-- | This module provides styles for borders as used in terminal
-- applications. Your mileage may vary on some of the fancier styles
-- due to varying support for some border characters in the fonts your
-- users may be using. Because of this, we provide the 'ascii' style in
-- addition to the Unicode styles. The 'unicode' style is also a safe
-- bet.
--
-- To use these in your widgets, see
-- 'Brick.Widgets.Core.withBorderStyle'. By default, widgets rendered
-- without a specified border style use 'unicode' style.
module Brick.Widgets.Border.Style
  ( BorderStyle(..)
  , borderStyleFromChar
  , ascii
  , unicode
  , unicodeBold
  , unicodeRounded
  , defaultBorderStyle
  )
where

import GHC.Generics
import Control.DeepSeq

-- | A border style for use in any widget that needs to render borders
-- in a consistent style.
data BorderStyle =
    BorderStyle { BorderStyle -> Char
bsCornerTL :: Char
                -- ^ Top-left corner character
                , BorderStyle -> Char
bsCornerTR :: Char
                -- ^ Top-right corner character
                , BorderStyle -> Char
bsCornerBR :: Char
                -- ^ Bottom-right corner character
                , BorderStyle -> Char
bsCornerBL :: Char
                -- ^ Bottom-left corner character
                , BorderStyle -> Char
bsIntersectFull :: Char
                -- ^ Full intersection (cross)
                , BorderStyle -> Char
bsIntersectL :: Char
                -- ^ Left side of a horizontal border intersecting a vertical one
                , BorderStyle -> Char
bsIntersectR :: Char
                -- ^ Right side of a horizontal border intersecting a vertical one
                , BorderStyle -> Char
bsIntersectT :: Char
                -- ^ Top of a vertical border intersecting a horizontal one
                , BorderStyle -> Char
bsIntersectB :: Char
                -- ^ Bottom of a vertical border intersecting a horizontal one
                , BorderStyle -> Char
bsHorizontal :: Char
                -- ^ Horizontal border character
                , BorderStyle -> Char
bsVertical :: Char
                -- ^ Vertical border character
                }
                deriving (Int -> BorderStyle -> ShowS
[BorderStyle] -> ShowS
BorderStyle -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BorderStyle] -> ShowS
$cshowList :: [BorderStyle] -> ShowS
show :: BorderStyle -> String
$cshow :: BorderStyle -> String
showsPrec :: Int -> BorderStyle -> ShowS
$cshowsPrec :: Int -> BorderStyle -> ShowS
Show, ReadPrec [BorderStyle]
ReadPrec BorderStyle
Int -> ReadS BorderStyle
ReadS [BorderStyle]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BorderStyle]
$creadListPrec :: ReadPrec [BorderStyle]
readPrec :: ReadPrec BorderStyle
$creadPrec :: ReadPrec BorderStyle
readList :: ReadS [BorderStyle]
$creadList :: ReadS [BorderStyle]
readsPrec :: Int -> ReadS BorderStyle
$creadsPrec :: Int -> ReadS BorderStyle
Read, BorderStyle -> BorderStyle -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BorderStyle -> BorderStyle -> Bool
$c/= :: BorderStyle -> BorderStyle -> Bool
== :: BorderStyle -> BorderStyle -> Bool
$c== :: BorderStyle -> BorderStyle -> Bool
Eq, 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
$cto :: forall x. Rep BorderStyle x -> BorderStyle
$cfrom :: forall x. BorderStyle -> Rep BorderStyle x
Generic, BorderStyle -> ()
forall a. (a -> ()) -> NFData a
rnf :: BorderStyle -> ()
$crnf :: BorderStyle -> ()
NFData)

defaultBorderStyle :: BorderStyle
defaultBorderStyle :: BorderStyle
defaultBorderStyle = BorderStyle
unicode

-- | Make a border style using the specified character everywhere.
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

-- |An ASCII border style which will work in any terminal.
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
'|'
                }

-- |A unicode border style with real corner and intersection characters.
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
'│'
                }

-- |A unicode border style in a bold typeface.
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
'┃'
                }

-- |A unicode border style with rounded corners.
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
'│'
                }