{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecursiveDo #-}
module Reflex.Vty.GHCi where
import Control.Monad ((<=<), void)
import Control.Monad.Fix (MonadFix)
import Control.Monad.IO.Class (liftIO, MonadIO)
import Data.ByteString (ByteString)
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import Reflex.Network
import Reflex.Process
import Reflex.Process.GHCi
import Reflex.Vty
import qualified Graphics.Vty.Input as V
import qualified System.Process as P
statusDisplay
:: ( PostBuild t m
, MonadHold t m
)
=> Ghci t
-> VtyWidget t m ()
statusDisplay g = do
pb <- getPostBuild
text <=< hold "" $ leftmost
[ statusMessage <$> updated (_ghci_status g)
, statusMessage <$> tag (current $ _ghci_status g) pb
, ("Command exited with " <>) . T.pack . show <$> _process_exit (_ghci_process g)
]
scrollableOutput
:: ( Reflex t
, MonadNodeId m
, MonadHold t m
, MonadFix m
, PostBuild t m
)
=> Behavior t ByteString
-> VtyWidget t m ()
scrollableOutput out = col $ do
dh <- displayHeight
scroll <- stretch $ scrollableText never $ T.decodeUtf8 <$> out
fixed 1 $ text $
let f h (ix, n) = if n - ix + 1 > h
then "↓ More ↓"
else ""
in f <$> current dh <*> scroll
scrollingOutput
:: ( Reflex t
, Monad m
, MonadHold t m
, MonadFix m
)
=> Dynamic t ByteString
-> VtyWidget t m ()
scrollingOutput out = do
dh <- displayHeight
let scrollBy h (ix, n) =
if | ix == 0 && n <= h -> Nothing
| n > h && n - ix - h == 0 -> Just 1
| otherwise -> Nothing
rec scroll <- scrollableText (tagMaybe (scrollBy <$> current dh <*> scroll) $ updated out) $
T.decodeUtf8 <$> current out
return ()
ghciModuleStatus
:: ( MonadNodeId m
, PostBuild t m
, MonadHold t m
, MonadFix m
, Adjustable t m
)
=> Ghci t
-> VtyWidget t m ()
ghciModuleStatus g = col $ do
let ghciExit = _process_exit $ _ghci_process g
ghciExited <- hold False $ True <$ ghciExit
fixed 3 $ boxStatic def $ statusDisplay g
out <- moduleOutput (not <$> ghciExited) g
stretch $ void $
networkHold (scrollableOutput $ current out) $ ffor (_ghci_reload g) $
const $ scrollableOutput $ current out
ghciExecOutput
:: ( MonadHold t m
, MonadFix m
, Adjustable t m
)
=> Ghci t
-> VtyWidget t m ()
ghciExecOutput g = do
ghciExited <- hold False $ True <$ _process_exit (_ghci_process g)
out <- execOutput (not <$> ghciExited) g
_ <- networkHold (scrollingOutput out) $ ffor (_ghci_reload g) $ \_ -> scrollingOutput out
return ()
ghciPanes
:: ( Reflex t
, MonadFix m
, MonadHold t m
, MonadNodeId m
, PostBuild t m
, Adjustable t m
)
=> Ghci t
-> VtyWidget t m ()
ghciPanes g = void $ splitVDrag
(hRule doubleBoxStyle)
(ghciModuleStatus g)
(ghciExecOutput g)
getExitEvent
:: ( PerformEvent t m
, MonadIO (Performable m)
)
=> Ghci t
-> Event t a
-> VtyWidget t m (Event t ())
getExitEvent g externalExitReq = do
exitReq <- keyCombo (V.KChar 'c', [V.MCtrl])
let exitReqs = leftmost
[ g <$ externalExitReq
, g <$ exitReq
]
shutdown exitReqs
shutdown
:: ( PerformEvent t m
, MonadIO (Performable m)
)
=> Event t (Ghci t)
-> m (Event t ())
shutdown exitReqs = do
performEvent $ ffor exitReqs $ \g ->
liftIO $ P.terminateProcess $ _process_handle $ _ghci_process g