{-# Language OverloadedStrings #-}
module Client.View.Digraphs (digraphLines) where
import Client.Image.Message (cleanChar)
import Client.Image.PackedImage
import Client.State
import Data.List
import Data.List.Split
import qualified Data.Text as Text
import qualified Data.Text.Lazy as LText
import Data.Text (Text)
import Digraphs
import Graphics.Vty.Attributes
import Graphics.Vty.Image (wcwidth, wcswidth)
digraphLines ::
Int ->
ClientState ->
[Image']
digraphLines w st
= map (mconcat . intersperse sep)
$ chunksOf entriesPerLine
$ map (text' defAttr)
$ matcher
$ map (Text.pack . drawEntry)
$ Text.chunksOf 3 digraphs
where
matcher = maybe id (\m -> filter (matcherPred m . LText.fromStrict)) (clientMatcher st)
entriesPerLine = max 1
$ (w + sepWidth) `quot` (entryWidth + sepWidth)
entryWidth :: Int
entryWidth = 5
sepWidth :: Int
sepWidth = imageWidth sep
sep :: Image'
sep = text' defAttr " "
drawEntry :: Text -> String
drawEntry entry = output ++ replicate (entryWidth - wcswidth output) ' '
where
[x,y,z] = Text.unpack entry
output = x:y:z2
dottedCircle = '\x25cc'
z1 = cleanChar z
z2 | wcwidth z1 == 0 = [' ', dottedCircle, z1]
| otherwise = [' ', z1]