mirror of
https://github.com/ilyakooo0/reflex-vty.git
synced 2024-11-30 01:04:16 +03:00
166 lines
5.8 KiB
Haskell
166 lines
5.8 KiB
Haskell
{-# LANGUAGE FlexibleContexts #-}
|
|
{-# LANGUAGE FlexibleInstances #-}
|
|
{-# LANGUAGE GADTs #-}
|
|
{-# LANGUAGE LambdaCase #-}
|
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
{-# LANGUAGE RankNTypes #-}
|
|
{-# LANGUAGE RecursiveDo #-}
|
|
{-# LANGUAGE ScopedTypeVariables #-}
|
|
{-# LANGUAGE TupleSections #-}
|
|
{-# OPTIONS_GHC -threaded #-}
|
|
|
|
import Control.Applicative
|
|
import Control.Monad.Fix
|
|
import Data.Map (Map)
|
|
import qualified Data.Map as Map
|
|
import Data.Text (Text)
|
|
import qualified Data.Text as T
|
|
import qualified Data.Text.Zipper as TZ
|
|
import qualified Graphics.Vty as V
|
|
import Reflex
|
|
import Reflex.Class.Switchable
|
|
import Reflex.NotReady.Class
|
|
import Reflex.Vty
|
|
|
|
main :: IO ()
|
|
main = mainWidget $ do
|
|
inp <- input
|
|
tellShutdown . fforMaybe inp $ \case
|
|
V.EvKey (V.KChar 'c') [V.MCtrl] -> Just ()
|
|
_ -> Nothing
|
|
let btn = button $ pure "Add another task"
|
|
rec let todos' = todos [Todo "First" True, Todo "Second" False, Todo "Third" False] $ leftmost
|
|
[ () <$ e
|
|
, fforMaybe inp $ \case
|
|
V.EvKey V.KEnter [] -> Just ()
|
|
_ -> Nothing
|
|
]
|
|
(m, (e, _)) <- splitV (pure (subtract 6)) (pure (True, True)) todos' $ do
|
|
splitV (pure (subtract 3)) (pure (True, True)) btn (display $ current m)
|
|
return ()
|
|
|
|
testBoxes :: (Reflex t, MonadHold t m, MonadFix m) => VtyWidget t m ()
|
|
testBoxes = do
|
|
size <- displaySize
|
|
let region1 = fmap (\(w,h) -> Region (w `div` 6) (h `div` 6) (w `div` 2) (h `div` 2)) size
|
|
region2 = fmap (\(w,h) -> Region (w `div` 4) (h `div` 4) (2 * (w `div` 3)) (2*(h `div` 3))) size
|
|
pane region1 (constDyn False) . box singleBoxStyle $ debugInput
|
|
_ <- pane region2 (constDyn True) . box singleBoxStyle $
|
|
splitVDrag (hRule doubleBoxStyle) (box roundedBoxStyle $ multilineTextInput def) (box roundedBoxStyle dragTest)
|
|
return ()
|
|
|
|
debugFocus :: (Reflex t, Monad m) => VtyWidget t m ()
|
|
debugFocus = do
|
|
f <- focus
|
|
text $ T.pack . show <$> current f
|
|
|
|
debugInput :: (Reflex t, MonadHold t m) => VtyWidget t m ()
|
|
debugInput = do
|
|
lastEvent <- hold "No event yet" . fmap show =<< input
|
|
text $ T.pack <$> lastEvent
|
|
|
|
dragTest :: (Reflex t, MonadHold t m, MonadFix m) => VtyWidget t m ()
|
|
dragTest = do
|
|
lastEvent <- hold "No event yet" . fmap show =<< drag V.BLeft
|
|
text $ T.pack <$> lastEvent
|
|
|
|
testStringBox :: (Reflex t, Monad m) => VtyWidget t m ()
|
|
testStringBox = box singleBoxStyle .
|
|
text . pure . T.pack . take 500 $ cycle ('\n' : ['a'..'z'])
|
|
|
|
data Todo = Todo
|
|
{ _todo_label :: Text
|
|
, _todo_done :: Bool
|
|
}
|
|
deriving (Show, Read, Eq, Ord)
|
|
|
|
checkbox
|
|
:: (MonadHold t m, MonadFix m, Reflex t)
|
|
=> Bool
|
|
-> VtyWidget t m (Dynamic t Bool)
|
|
checkbox v0 = do
|
|
i <- input
|
|
v <- toggle v0 $ fforMaybe i $ \case
|
|
V.EvMouseUp _ _ _ -> Just ()
|
|
_ -> Nothing
|
|
text $ current $ ffor v $ \v' -> if v' then "[x]" else "[ ]"
|
|
return v
|
|
|
|
button :: (Reflex t, Monad m) => Behavior t Text -> VtyWidget t m (Event t ())
|
|
button t = do
|
|
box roundedBoxStyle $ text t
|
|
fmap (() <$) mouseUp
|
|
|
|
data TodoOutput t = TodoOutput
|
|
{ _todoOutput_todo :: Dynamic t Todo
|
|
, _todoOutput_delete :: Event t ()
|
|
}
|
|
|
|
instance Reflex t => Switchable t (TodoOutput t) where
|
|
switching t0 e = TodoOutput
|
|
<$> switching (_todoOutput_todo t0) (_todoOutput_todo <$> e)
|
|
<*> switching (_todoOutput_delete t0) (_todoOutput_delete <$> e)
|
|
|
|
todo
|
|
:: (MonadHold t m, MonadFix m, Reflex t)
|
|
=> Todo
|
|
-> VtyWidget t m (TodoOutput t)
|
|
todo t0 = do
|
|
w <- displayWidth
|
|
let checkboxWidth = 3
|
|
checkboxRegion = pure $ Region 0 0 checkboxWidth 1
|
|
labelRegion = ffor w $ \w' -> Region (checkboxWidth + 1) 0 (w' - 1 - checkboxWidth) 1
|
|
value <- pane checkboxRegion (pure True) $ checkbox $ _todo_done t0
|
|
(label, d) <- pane labelRegion (pure True) $ do
|
|
i <- input
|
|
v <- textInput $ def { _textInputConfig_initialValue = TZ.fromText $ _todo_label t0 }
|
|
let deleteSelf = attachWithMaybe backspaceOnEmpty (current v) i
|
|
return (v, deleteSelf)
|
|
return $ TodoOutput
|
|
{ _todoOutput_todo = Todo <$> label <*> value
|
|
, _todoOutput_delete = d
|
|
}
|
|
where
|
|
backspaceOnEmpty v = \case
|
|
V.EvKey V.KBS _ | T.null v -> Just ()
|
|
_ -> Nothing
|
|
|
|
todos
|
|
:: forall t m. (MonadHold t m, MonadFix m, Reflex t, Adjustable t m, NotReady t m, PostBuild t m)
|
|
=> [Todo]
|
|
-> Event t ()
|
|
-> VtyWidget t m (Dynamic t (Map Int Todo))
|
|
todos todos0 newTodo = do
|
|
let todosMap0 = Map.fromList $ zip [0..] todos0
|
|
w <- displayWidth
|
|
rec listOut <- listHoldWithKey todosMap0 updates $ \row t -> do
|
|
let reg = zipDynWith (\w' ts ->
|
|
let l = Map.size $ Map.takeWhileAntitone (<row) ts
|
|
in Region 0 l w' 1) w todosMap
|
|
pane reg (fmap (==row) selected) $ do
|
|
e <- mouseUp
|
|
r <- todo t
|
|
return (row <$ e, r)
|
|
let selectionClick = switch . current $ fmap (leftmost . Map.elems . fmap fst) listOut
|
|
selected <- holdDyn 0 $ leftmost
|
|
[ selectionClick
|
|
, fmapMaybe (fmap fst . Map.lookupMax) insert
|
|
, selectOnDelete
|
|
]
|
|
let todosMap = joinDynThroughMap $ fmap (fmap (_todoOutput_todo . snd)) listOut
|
|
todoDelete = switch . current $
|
|
leftmost . Map.elems . Map.mapWithKey (\k -> (k <$) . _todoOutput_delete . snd) <$> listOut
|
|
selectOnDelete = attachWithMaybe
|
|
(\m k -> let (before, after) = Map.split k m
|
|
in fmap fst $ Map.lookupMax before <|> Map.lookupMin after)
|
|
(current todosMap)
|
|
todoDelete
|
|
insert = ffor (tag (current todosMap) newTodo) $ \m -> case Map.lookupMax m of
|
|
Nothing -> Map.singleton 0 $ Just $ Todo "" False
|
|
Just (k, _) -> Map.union (Just <$> m) $ Map.singleton (k+1) $ Just $ Todo "" False
|
|
delete = ffor (attach (current todosMap) todoDelete) $ \(m, k) ->
|
|
Map.union (Map.singleton k Nothing) $ Just <$> m
|
|
updates = leftmost [insert, delete]
|
|
return todosMap
|