module UI.Widgets.Spade.Input where import qualified Data.Text as T import qualified System.Console.ANSI as A import Common import DiffRender.DiffRender import UI.Chars import UI.Widgets.Common import UI.Widgets.Editor data InputWidget = InputWidget { iwEditor :: WRef EditorWidget , iwFocused :: Bool } instance Widget InputWidget where -- hasCapability (ContainerCap _ (_ :: Proxy cnt)) = case eqT @cnt @Text of -- Just Refl -> Just Dict -- Nothing -> Nothing hasCapability (DrawableCap _) = Just Dict hasCapability (MoveableCap _) = Just Dict hasCapability (FocusableCap _) = Just Dict hasCapability (KeyInputCap _) = Just Dict hasCapability _ = Nothing instance Drawable InputWidget where draw ref = do w <- readWRef ref let ed = iwEditor w pos <- moveLeft 1 <$> getPos ed dim <- getDim ed let styleFn = if iwFocused w then (\x -> StyledText (Fg A.Red) [Plain x]) else Plain forM_ [0..(diH dim - 1)] (\r -> do wSetCursor $ moveDown r pos csPutText $ styleFn $ T.singleton verticalLine ) draw ed getVisibility ref = (iwEditor <$> readWRef ref) >>= getVisibility setVisibility ref v =(iwEditor <$> readWRef ref) >>= (flip setVisibility v) instance Moveable InputWidget where getPos ref = iwEditor <$> (readWRef ref) >>= getPos >>= (pure . moveLeft 1) move ref pos = (iwEditor <$> readWRef ref) >>= (flip move (moveRight 1 pos)) getDim ref = iwEditor <$> (readWRef ref) >>= getDim >>= (pure . amendWidth (\x -> x + 1)) resize ref cb = (iwEditor <$> readWRef ref) >>= (flip resize (amendWidth (\x -> x - 1) . cb)) instance Focusable InputWidget where setFocus ref b = modifyWRef ref (\w -> w { iwFocused = b }) getFocus ref =(iwFocused <$> readWRef ref) instance KeyInput InputWidget where getCursorInfo _ = pure Nothing handleInput ref ev = do ed <- iwEditor <$> readWRef ref handleInput ed ev draw ref input :: WidgetC m => Dimensions -> m (WRef InputWidget) input dim = do ew <- editor (\_ -> pure []) Nothing modifyWRef ew (\e -> e { ewParams = EditorParams 0 0 0 False False }) resize ew (\_ -> amendWidth (\x -> x - 1) dim) newWRef $ InputWidget ew False