{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecursiveDo #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Reflex.Vty.Widget.Input.Text
( module Reflex.Vty.Widget.Input.Text
, def
) where
import Control.Monad (join)
import Control.Monad.Fix (MonadFix)
import Control.Monad.NodeId (MonadNodeId)
import Data.Default (Default(..))
import Data.Text (Text)
import Data.Text.Zipper
import qualified Graphics.Vty as V
import Reflex
import Reflex.Vty.Widget
import Reflex.Vty.Widget.Layout
data TextInputConfig t = TextInputConfig
{ _textInputConfig_initialValue :: TextZipper
, _textInputConfig_modify :: Event t (TextZipper -> TextZipper)
, _textInputConfig_tabWidth :: Int
}
instance Reflex t => Default (TextInputConfig t) where
def = TextInputConfig empty never 4
data TextInput t = TextInput
{ _textInput_value :: Dynamic t Text
, _textInput_lines :: Dynamic t Int
}
textInput
:: (Reflex t, MonadHold t m, MonadFix m)
=> TextInputConfig t
-> VtyWidget t m (TextInput t)
textInput cfg = do
i <- input
f <- focus
dh <- displayHeight
dw <- displayWidth
rec v <- foldDyn ($) (_textInputConfig_initialValue cfg) $ mergeWith (.)
[ uncurry (updateTextZipper (_textInputConfig_tabWidth cfg)) <$> attach (current dh) i
, _textInputConfig_modify cfg
, let displayInfo = (,) <$> current rows <*> scrollTop
in ffor (attach displayInfo click) $ \((dl, st), MouseDown _ (mx, my) _) ->
goToDisplayLinePosition mx (st + my) dl
]
click <- mouseDown V.BLeft
let cursorAttrs = ffor f $ \x -> if x then cursorAttributes else V.defAttr
let rows = (\w s c -> displayLines w V.defAttr c s) <$> dw <*> v <*> cursorAttrs
img = images . _displayLines_spans <$> rows
y <- holdUniqDyn $ _displayLines_cursorY <$> rows
let newScrollTop :: Int -> (Int, Int) -> Int
newScrollTop st (h, cursorY)
| cursorY < st = cursorY
| cursorY >= st + h = cursorY - h + 1
| otherwise = st
let hy = attachWith newScrollTop scrollTop $ updated $ zipDyn dh y
scrollTop <- hold 0 hy
tellImages $ (\imgs st -> (:[]) . V.vertCat $ drop st imgs) <$> current img <*> scrollTop
return $ TextInput
{ _textInput_value = value <$> v
, _textInput_lines = length . _displayLines_spans <$> rows
}
multilineTextInput
:: (Reflex t, MonadHold t m, MonadFix m)
=> TextInputConfig t
-> VtyWidget t m (TextInput t)
multilineTextInput cfg = do
i <- input
textInput $ cfg
{ _textInputConfig_modify = mergeWith (.)
[ fforMaybe i $ \case
V.EvKey V.KEnter [] -> Just $ insert "\n"
_ -> Nothing
, _textInputConfig_modify cfg
]
}
textInputTile
:: (Reflex t, MonadHold t m, MonadFix m, MonadNodeId m)
=> VtyWidget t m (TextInput t)
-> Dynamic t Int
-> Layout t m (TextInput t)
textInputTile txt width = do
o <- askOrientation
rec t <- fixed sz txt
let sz = join $ ffor o $ \case
Orientation_Column -> _textInput_lines t
Orientation_Row -> width
return t
cursorAttributes :: V.Attr
cursorAttributes = V.withStyle V.defAttr V.reverseVideo
images :: [[Span V.Attr]] -> [V.Image]
images = map (V.horizCat . map spanToImage)
image :: [[Span V.Attr]] -> V.Image
image = V.vertCat . images
spanToImage :: Span V.Attr -> V.Image
spanToImage (Span attrs t) = V.text' attrs t
updateTextZipper
:: Int
-> Int
-> V.Event
-> TextZipper
-> TextZipper
updateTextZipper tabWidth pageSize ev = case ev of
V.EvKey (V.KChar '\t') [] -> tab tabWidth
V.EvKey (V.KChar k) [] -> insertChar k
V.EvKey V.KBS [] -> deleteLeft
V.EvKey V.KDel [] -> deleteRight
V.EvKey (V.KChar 'u') [V.MCtrl] -> const empty
V.EvKey (V.KChar 'w') [V.MCtrl] -> deleteLeftWord
V.EvKey V.KLeft [] -> left
V.EvKey V.KRight [] -> right
V.EvKey V.KUp [] -> up
V.EvKey V.KDown [] -> down
V.EvKey V.KHome [] -> home
V.EvKey V.KEnd [] -> end
V.EvKey V.KPageUp [] -> pageUp pageSize
V.EvKey V.KPageDown [] -> pageDown pageSize
_ -> id