{-# LANGUAGE OverloadedStrings #-}
module Cursor.Brick.Text where
import Brick.Types as Brick
import Brick.Widgets.Core as Brick
import Cursor.Text
import Data.Text (Text)
import qualified Data.Text as T
selectedTextCursorWidget :: n -> TextCursor -> Widget n
selectedTextCursorWidget :: n -> TextCursor -> Widget n
selectedTextCursorWidget n
n TextCursor
tc =
  n -> Location -> Widget n -> Widget n
forall n. n -> Location -> Widget n -> Widget n
Brick.showCursor n
n ((Int, Int) -> Location
Brick.Location (TextCursor -> Int
textCursorIndex TextCursor
tc, Int
0)) (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$
    TextCursor -> Widget n
forall n. TextCursor -> Widget n
textCursorWidget TextCursor
tc
textCursorWidget :: TextCursor -> Widget n
textCursorWidget :: TextCursor -> Widget n
textCursorWidget TextCursor
tc =
  Text -> Widget n
forall n. Text -> Widget n
txt (Text -> Widget n) -> Text -> Widget n
forall a b. (a -> b) -> a -> b
$
    let t :: Text
t = Text -> Text
sanitiseText (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ TextCursor -> Text
rebuildTextCursor TextCursor
tc
     in if Text -> Bool
T.null Text
t
          then Text
" "
          else Text
t
textWidget :: Text -> Widget n
textWidget :: Text -> Widget n
textWidget = Text -> Widget n
forall n. Text -> Widget n
txt (Text -> Widget n) -> (Text -> Text) -> Text -> Widget n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
nonNullLinesText (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
sanitiseText
textWidgetWrap :: Text -> Widget n
textWidgetWrap :: Text -> Widget n
textWidgetWrap = Text -> Widget n
forall n. Text -> Widget n
txtWrap (Text -> Widget n) -> (Text -> Text) -> Text -> Widget n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
nonNullLinesText (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
sanitiseText
textLineWidget :: Text -> Widget n
textLineWidget :: Text -> Widget n
textLineWidget = Text -> Widget n
forall n. Text -> Widget n
txt (Text -> Widget n) -> (Text -> Text) -> Text -> Widget n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
nonNullText (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
sanitiseText
textLineWidgetWrap :: Text -> Widget n
textLineWidgetWrap :: Text -> Widget n
textLineWidgetWrap = Text -> Widget n
forall n. Text -> Widget n
txtWrap (Text -> Widget n) -> (Text -> Text) -> Text -> Widget n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
nonNullText (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
sanitiseText
nonNullLinesText :: Text -> Text
nonNullLinesText :: Text -> Text
nonNullLinesText = Text -> [Text] -> Text
T.intercalate Text
"\n" ([Text] -> Text) -> (Text -> [Text]) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Text
nonNullText ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> [Text]
T.splitOn Text
"\n"
nonNullText :: Text -> Text
nonNullText :: Text -> Text
nonNullText Text
"" = Text
" "
nonNullText Text
t = Text
t
sanitiseText :: Text -> Text
sanitiseText :: Text -> Text
sanitiseText =
  (Char -> Char) -> Text -> Text
T.map ((Char -> Char) -> Text -> Text) -> (Char -> Char) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ \Char
c ->
    case Char
c of
      Char
'\t' -> Char
' '
      Char
_ -> Char
c