module IDE.IDE where import Common import Compiler.Lexer import Compiler.Parser import Control.Concurrent import Control.Concurrent.STM (TChan, TVar, atomically, dupTChan, modifyTVar, newTChan, newTChanIO, newTVarIO, readTChan, readTVar, readTVarIO, writeTChan, writeTVar) import Control.Exception import Control.Monad import Data.IORef import qualified Data.List as DL import Data.Map as Map import Data.Maybe import qualified Data.Set as S import Data.Text as T import Data.Text.IO as T import Compiler.AST.Program import IDE.Common import IDE.Help import Interpreter import Interpreter.Common import Interpreter.Initialize import Parser.Parser import UI.Widgets import UI.Widgets.AutoComplete import UI.Widgets.Layout import UI.Widgets.LogWidget import UI.Widgets.WatchWidget data IDEState = IDEState { idsDebugThreadId :: Maybe ThreadId , idsDebugIn :: Maybe (MVar DebugIn) , idsDebugOut :: Maybe (MVar DebugOut) , idsDebugThreadInput :: Maybe (TChan TerminalEvent) , idsCodeAutocompletions :: [(Text, Text)] , idsCodeParseError :: Maybe (Location, Text) , idsKeyInputReciever :: Maybe SomeKeyInputWidget } ideStartState :: IDEState ideStartState = IDEState Nothing Nothing Nothing Nothing [] Nothing Nothing type Clipboard = (Text -> IO (), IO (Maybe Text)) type IDEM a = WidgetM IO a editorId :: Text editorId = "editor" watchWidgetId :: Text watchWidgetId = "watch" extractBuiltIns :: IO ([(Text, Text)], [(Text, Text)]) extractBuiltIns = do debugIn <- newEmptyMVar debugOut <- newEmptyMVar sdlWindowsRef <- newIORef [] scope <- isGlobalScope . snd <$> runStateT loadBuiltIns (emptyIs sdlWindowsRef debugIn debugOut (error "Input stream not available")) let keywords = (\x -> let s = toSource $ toEnum @Keyword x in (s, s)) <$> [0 .. fromEnum $ maxBound @Keyword] let builtIns = DL.foldl' extractOneDoc [] (Map.assocs scope) pure $ (keywords, builtIns) where extractOneDoc :: [(Text, Text)] -> (ScopeKey, Value) -> [(Text, Text)] extractOneDoc in_ (SkIdentifier (unIdentifer ->ide), BuiltIn (BuiltinVal (ObjectValue m))) = in_ <> ((\k -> let a = ide <> "." <> k in (a, a)) <$> Map.keys m) extractOneDoc in_ (SkIdentifier ide, BuiltIn (BuiltinCallWithDoc s)) = (unIdentifer ide, T.concat [ unIdentifer ide, "(", T.intercalate ", " ((\(l, r) -> T.concat [l, ": ", r]) <$> extractDoc s), ")" ] ) : in_ extractOneDoc in_ (SkIdentifier ide, BuiltIn (BuiltinCall _)) = (unIdentifer ide, unIdentifer ide) : in_ extractOneDoc in_ (SkOperator op, _) = (toSource op, toSource op) : in_ extractOneDoc in_ _ = in_ getAutocompleteSuggestions :: MonadIO m => TVar IDEState -> [(Text, Text)] -> Text -> m [(Text, Text)] getAutocompleteSuggestions ideStateRef dict key = do acs <- liftIO $ idsCodeAutocompletions <$> readTVarIO ideStateRef pure $ Prelude.filter fn (acs <> dict) where fn :: (Text, Text) -> Bool fn (i, _) = T.isPrefixOf key i getTerminalSize' :: IO Dimensions getTerminalSize' = do s <- getTerminalSizeIO case s of Just (xs, ys) -> pure $ Dimensions xs ys _ -> error "Cannot read terminal size" -- This thread reads the editor contents and try to parse into -- tokens and ast. And then fills some autocomplete suggestions and -- makes any parse error location. codeProcessingThread :: IORef [Token] -> TChan IDEEvent -> MVar Text -> IO () codeProcessingThread tokensRef ideEventRef editorContentRef = forever $ do liftIO $ atomically $ writeTChan ideEventRef IDEReqEditorContent code <- takeMVar editorContentRef tokens <- tokenize code liftIO $ writeIORef tokensRef tokens mError <- parseEither @Program tokens >>= \case Left (ParseErrorWithParsed _ loc (FatalError a)) -> pure $ Just (loc, T.pack $ show a) Left (ParseErrorWithParsed _ _ (FatalErrorWithLocation loc fpe)) -> pure $ Just (loc, T.pack $ show fpe) _ -> pure Nothing liftIO $ atomically $ writeTChan ideEventRef $ IDEParseErrorUpdate mError liftIO $ atomically $ writeTChan ideEventRef $ IDEACUpdateIdentifiers $ S.toList $ S.fromList $ catMaybes $ filterIdentifiers <$> tokens wait 1 where filterIdentifiers :: Token -> Maybe Text filterIdentifiers Token { tkRaw = (TkIdentifier (unIdentifer -> idf))} = Just idf filterIdentifiers _ = Nothing -- | A type to differentiat debuging mode in IDE when input events -- need to be fed to the interpreted program, and not to the IDE. data InputRouting = RouteIDE | RouteProgram (TChan TerminalEvent) instance Show InputRouting where show RouteIDE = "Route To IDE" show (RouteProgram _) = "Route To Program" runIDE :: FilePath -> TChan TerminalEvent -> IO () runIDE filePath inputBroadcastChan = do dim <- getTerminalSize' content <- try (T.readFile filePath) >>= \case Right c -> pure c Left (_ :: SomeException) -> pure "" (keywords, builtIns) <- extractBuiltIns ideStateRef <- newTVarIO ideStartState ideEventsRef <- liftIO newTChanIO clipboardRef <- newIORef @(Maybe Text) Nothing let clipboard = (\t -> modifyIORef clipboardRef (\_ -> Just t), readIORef clipboardRef) editorContentMVar <- newEmptyMVar @Text tokensRef <- newIORef @[Token] [] void $ forkIO $ codeProcessingThread tokensRef ideEventsRef editorContentMVar inputRouteToRef <- newTVarIO RouteIDE inputChan <- liftIO $ atomically $ dupTChan inputBroadcastChan void $ liftIO $ forkIO $ forever $ do (atomically $ readTVar inputRouteToRef) >>= appendLog atomically $ do kv <- readTChan inputChan readTVar inputRouteToRef >>= \case RouteIDE -> writeTChan ideEventsRef (IDETerminalEvent kv) RouteProgram chan -> writeTChan chan kv void $ runWidgetM $ do -- The editor editorRef <- editor (getAutocompleteSuggestions ideStateRef (keywords <> ((\(a, b) -> (a <>"()", b)) <$> builtIns))) (Just $ SomeTokenStream (readIORef tokensRef)) setContent editorRef content liftIO $ atomically $ modifyTVar ideStateRef (\ids -> ids { idsKeyInputReciever = Just $ SomeKeyInputWidget editorRef }) -- Watch widget watchWidgetRef <- watchWidget let dimensionDistributionFn = \case 1 -> [1] 2 -> [0.85, 0.15] 3 -> [0.70, 0.15, 0.15] a -> error $ "Unsupported widget count:" <> show a watchAndLogLayout <- layoutWidget Horizontal dimensionDistributionFn Nothing logRef <- logWidget insertLog logRef "Welcome to S.P.A.D.E: The Simple Programming And Debugging Environment." insertLog logRef "By Sandeep.C.R" addWidget watchAndLogLayout "log" logRef addWidget watchAndLogLayout watchWidgetId watchWidgetRef helpWidgetRef <- helpWidget ((Prelude.head . T.split (== '.'). fst) <$> builtIns) ideEventsRef -- The autocomplete widget ac <- autoComplete modifyWRef editorRef (\ed -> ed { ewAutocompleteWidget = Just $ SomeWidgetRef ac }) -- The Outermost layout layoutRef <- layoutWidget Vertical dimensionDistributionFn (Just $ SomeKeyInputWidget editorRef) modifyWRef layoutRef (\lw -> lw { lowFloatingContent = Just $ SomeWidgetRef ac }) addWidget layoutRef editorId editorRef addWidget layoutRef "helpwidget" helpWidgetRef addWidget layoutRef "watchandlog" watchAndLogLayout setVisibility helpWidgetRef False setTextFocus layoutRef editorId -- The menu let menu = Menu [ ("File", SubMenu ["Save (F6)", "Beautify", "Exit"]) , ("Edit", SubMenu ["Cut", "Copy", "Paste", "Select All"]) , ("Run", SubMenu ["Run (F5)", "Step (Ctrl+F8)"]) , ("Windows", SubMenu ["Clear log"]) , ("Help", SubMenu ["Contents"]) ] Nothing menuContainerRef <- menuContainer (SomeWidgetRef layoutRef) menu (selectionHandler ideEventsRef) modifyWRef menuContainerRef (\mc -> mc { mcwDim = dim }) modify (\ws -> ws { wsCursorWidget = Just $ SomeKeyInputWidget editorRef }) -- Initial screen paint csInitialize dim draw menuContainerRef csDraw -- A snippet that refresh the screen. let ideRedraw = do csClear draw menuContainerRef csDraw let getActiveEditor = do (getVisibility editorRef) >>= \case True -> pure editorRef _ -> getVisibility helpWidgetRef >>= \case True -> hwContentWidget <$> (readWRef helpWidgetRef) _ -> error "No visible editor" let launchProgram = do source <- getContent editorRef liftIO (compileEither source >>= \case Right p -> do debugIn <- newEmptyMVar debugOut <- newEmptyMVar programInputChan <- liftIO $ atomically newTChan threadId <- forkOS (void $ do liftIO $ atomically $ do writeTVar inputRouteToRef (RouteProgram programInputChan) interpret debugIn debugOut programInputChan p) atomically $ modifyTVar ideStateRef (\idestate -> idestate { idsDebugThreadId = Just threadId , idsDebugIn = Just debugIn , idsDebugOut = Just debugOut , idsDebugThreadInput = Just programInputChan }) pure $ Right (threadId, debugIn, debugOut, programInputChan) Left err -> do pure $ Left (hReadable err) ) uiLoop ideEventsRef (\case IDEToggleHelp -> do getVisibility helpWidgetRef >>= \case True -> do setVisibility helpWidgetRef False setVisibility editorRef True setVisibility watchAndLogLayout True modify (\ws -> ws { wsCursorWidget = Just $ SomeKeyInputWidget editorRef }) liftIO $ atomically (modifyTVar ideStateRef (\is -> is { idsKeyInputReciever = Just $ SomeKeyInputWidget editorRef })) False -> do setVisibility helpWidgetRef True setVisibility editorRef False setVisibility watchAndLogLayout False modify (\ws -> ws { wsCursorWidget = Just $ SomeKeyInputWidget helpWidgetRef }) liftIO $ atomically (modifyTVar ideStateRef (\is -> is { idsKeyInputReciever = Just $ SomeKeyInputWidget helpWidgetRef })) d <- getScreenBounds csInitialize d draw menuContainerRef csDraw pure True IDESave -> do c <- getContent editorRef liftIO $ T.writeFile filePath c insertLog logRef ("Saved to " <> (T.pack filePath) <>".") pure True IDEEdit Copy -> do ew <- getActiveEditor >>= readWRef case ewSelection ew of Just (r1, r2) -> let contents = ewContent ew removeLength = (r2 - r1 + 1) copyContent = T.take (removeLength + 1) (T.drop r1 contents) in liftIO $ (fst clipboard) copyContent Nothing -> pass pure True IDEEdit Cut -> do modifyWRefM editorRef (\ew -> case ewSelection ew of Just (r1, r2) -> let contents = ewContent ew (p1, p2) = T.splitAt r1 contents removeLength = (r2 - r1 + 1) cutContent = T.take removeLength p2 in do liftIO $ (fst clipboard) cutContent let newCursor = max 0 (r1 - 1) pure $ putCursor Nothing newCursor $ ew { ewSelection = Nothing, ewContent = p1 <> (T.drop removeLength p2) } Nothing -> pure ew ) ideRedraw pure True IDEEdit Paste -> do modifyWRefM editorRef (\ew -> do let contents = ewContent ew (p1, p2) = T.splitAt (ewCursor ew) contents (liftIO (snd clipboard)) >>= \case Nothing -> pure ew Just insertContent -> pure $ putCursor Nothing (ewCursor ew + T.length insertContent) $ ew { ewContent = p1 <> insertContent <> p2 } ) ideRedraw pure True IDEEdit SelectAll -> do modifyWRef editorRef (\ew -> ew { ewSelection = Just (0, (T.length $ ewContent ew) - 1) }) ideRedraw pure True IDEClearLog -> do modifyWRef logRef (\lw -> lw { lwContent = [], lwScrollOffset = 0 }) pure True IDEBeautify -> do insertLog logRef "Formatting..." code <- getContent editorRef (liftIO $ compileEither @Program code) >>= \case Right a -> do setContent editorRef (T.strip $ toSource a) liftIO $ atomically $ writeTChan ideEventsRef IDEDraw Left (ParseErrorWithParsed _ _ e) -> insertLog logRef ("Parse error:" <> T.pack (show e)) pure True IDEDraw -> do d <- getScreenBounds csInitialize d draw menuContainerRef csDraw pure True IDEACUpdateIdentifiers acs -> do liftIO $ atomically (modifyTVar ideStateRef (\is -> is { idsCodeAutocompletions = (\x -> (x, x)) <$> acs })) pure True IDEParseErrorUpdate mError -> do liftIO $ atomically (modifyTVar ideStateRef (\is -> is { idsCodeParseError = mError })) idestate <- liftIO $ readTVarIO ideStateRef case idsCodeParseError idestate of Just (loc, _) -> modifyWRef editorRef (\ew -> ew { ewParseErrorLocation = Just loc }) Nothing -> modifyWRef editorRef (\ew -> ew { ewParseErrorLocation = Nothing }) ideRedraw pure True IDEReqEditorContent -> do c <- getContent editorRef liftIO $ void $ putMVar editorContentMVar c pure True IDEExit -> do pure False IDERun -> do (\x' -> (idsDebugThreadId x', idsDebugIn x', idsDebugOut x', idsDebugThreadInput x')) <$> liftIO (readTVarIO ideStateRef) >>= \case -- If we are in a debug session, just run to completion. (Just threadId, Just debugIn, Just debugOut, Just programInputChan) -> do insertLog logRef "Continuing debug session to end..." executeAndUpdateIDEDebugState inputRouteToRef logRef editorRef ideEventsRef ideStateRef (Just Run) threadId debugIn debugOut programInputChan _ -> do -- Or else launch a new run of the program. clearscreen setCursorPosition 0 0 launchProgram >>= \case Right (threadId, debugIn, debugOut, programInputChan) -> do insertLog logRef "Starting..." executeAndUpdateIDEDebugState inputRouteToRef logRef editorRef ideEventsRef ideStateRef (Just Run) threadId debugIn debugOut programInputChan Left err -> do insertLog logRef $ "Compile Error:" <> err liftIO $ atomically $ writeTChan ideEventsRef IDEDraw pure True IDEStep -> do csSetCursorPosition 0 0 (\x' -> (idsDebugThreadId x', idsDebugIn x', idsDebugOut x', idsDebugThreadInput x')) <$> liftIO (readTVarIO ideStateRef) >>= \case -- A debugging session exists already. -- Send the step command, wait for updated state to arrive. (Just threadId, Just debugIn, Just debugOut, Just programInputChan) -> executeAndUpdateIDEDebugState inputRouteToRef logRef editorRef ideEventsRef ideStateRef (Just StepIn) threadId debugIn debugOut programInputChan _ -> do -- No debugging session exist. Launch one. launchProgram >>= \case Right (threadId, debugIn, debugOut, programInputChan) -> do insertLog logRef "Starting..." executeAndUpdateIDEDebugState inputRouteToRef logRef editorRef ideEventsRef ideStateRef Nothing threadId debugIn debugOut programInputChan Left err -> insertLog logRef $ "Compile Error:" <> err pure True IDETerminalEvent (TerminalResize w h) -> do let dim' = Dimensions w h csInitialize dim' modifyWRef menuContainerRef (\mc -> mc { mcwDim = dim' }) draw menuContainerRef adjustScrollOffset editorRef draw menuContainerRef csDraw pure True IDEDebugUpdate mds -> do case mds of Just ds -> do modifyWRef editorRef (\ew -> ew { ewReadOnly = True, ewDebugLocation = Just $ dsLocation ds, ewCursor = lcOffset (dsLocation ds) - 1 }) modifyWRef watchWidgetRef (\ww -> ww { wwVisible = True, wwContent = scopeToWatchItems $ dsScope ds }) case dsCurrenEvaluation ds of Just cv -> insertLog logRef ("Evaluating: " <> cv) Nothing -> pass Nothing -> do modifyWRef editorRef (\ew -> ew { ewReadOnly = False, ewDebugLocation = Nothing }) modifyWRef watchWidgetRef (\ww -> ww { wwVisible = False }) liftIO $ atomically $ writeTChan ideEventsRef IDEDraw pure True IDETerminalEvent (TerminalKey ev) -> case ev of KeyChar True _ _ 'c' -> pure False KeyChar True _ _ 'C' -> pure False k -> do updateMenuOnKey menuContainerRef k >>= \case True -> pure () False -> shortcutsHandler ideEventsRef k >>= \case True -> pure () False -> idsKeyInputReciever <$> (liftIO $ readTVarIO ideStateRef) >>= \case Just (SomeKeyInputWidget w) -> handleInput w k Nothing -> pure () idestate <- liftIO $ readTVarIO ideStateRef case idsCodeParseError idestate of Just (loc, _) -> modifyWRef editorRef (\ew -> ew { ewParseErrorLocation = Just loc }) Nothing -> modifyWRef editorRef (\ew -> ew { ewParseErrorLocation = Nothing }) ideRedraw pure True ) where executeAndUpdateIDEDebugState inputRouteToRef logRef editorRef ideEventRef ideStateRef mcmd threadId debugIn debugOut programInputChan = do case mcmd of Just cmd -> do liftIO $ do -- Empty out any pending debug message, and discard it. void $ tryTakeMVar debugOut -- before sending in a debug input. atomically $ writeTVar inputRouteToRef (RouteProgram programInputChan) putMVar debugIn cmd _ -> pure () (liftIO (catch (do dd <- takeMVar debugOut atomically $ writeTVar inputRouteToRef RouteIDE pure dd ) -- Possibly handle a control-c triggered by user to break -- a long runing operation. (\(e :: SomeException) -> do killThread threadId pure $ Errored $ T.pack $ show e ) )) >>= \case -- Update the IDE debug state with the received debug state. DebugData ds -> do liftIO $ atomically $ writeTChan ideEventRef (IDEDebugUpdate $ Just ds) Errored err -> do liftIO $ atomically $ modifyTVar ideStateRef (\i -> ideStartState { idsKeyInputReciever = idsKeyInputReciever i }) modifyWRef editorRef (\ew -> ew { ewReadOnly = False }) insertLog logRef err liftIO $ atomically $ do writeTChan ideEventRef (IDEDebugUpdate Nothing) Finished -> do modifyWRef editorRef (\ew -> ew { ewReadOnly = False }) liftIO $ atomically $ modifyTVar ideStateRef (\i -> ideStartState { idsKeyInputReciever = idsKeyInputReciever i }) insertLog logRef "Finished program" liftIO $ atomically $ do writeTChan ideEventRef (IDEDebugUpdate Nothing) updateMenuOnKey :: WidgetC m => WRef MenuContainerWidget -> KeyEvent -> m Bool updateMenuOnKey ref kv = do w <- readWRef ref case (kv, menuActive $ mcwMenu w) of (KeyCtrl _ _ _ Esc, Just _) -> do modifyWRef ref (\w' -> w' { mcwMenu = (mcwMenu w) { menuActive = Nothing }}) setCursorVisibility True pure True (KeyChar _ _ True c, _) -> do foldM_ (\x (n, _) -> case T.uncons (T.toLower n) of Nothing -> pure $ x + 1 Just (c1, _) -> if c == c1 then do modifyWRef ref (\w' -> w' { mcwMenu = (mcwMenu w) { menuActive = Just (x, 0) }}) setCursorVisibility False pure $ x + 1 else pure $ x + 1) 0 (menuItems $ mcwMenu w) pure True (KeyCtrl _ _ _ ArrowLeft, Just (x, _)) | x > 0 -> do modifyWRef ref (\w' -> w' { mcwMenu = (mcwMenu w) { menuActive = Just (x - 1, 0) }}) pure True | otherwise -> do modifyWRef ref (\w' -> w' { mcwMenu = (mcwMenu w) { menuActive = Just (Prelude.length (menuItems $ mcwMenu w) - 1, 0) }}) pure True (KeyCtrl _ _ _ ArrowRight, Just (x, _)) -> do let menuItemsLength = Prelude.length $ menuItems $ mcwMenu w let newX = x + 1 if newX < menuItemsLength then do modifyWRef ref (\w' -> w' { mcwMenu = (mcwMenu w) { menuActive = Just (newX, 0) }}) pure True else do modifyWRef ref (\w' -> w' { mcwMenu = (mcwMenu w) { menuActive = Just (0, 0) }}) pure True (KeyCtrl _ _ _ ArrowUp, Just (x, y)) | y > 0 -> do modifyWRef ref (\w' -> w' { mcwMenu = (mcwMenu w) { menuActive = Just (x, y - 1) }}) pure True | otherwise -> do case getSubmenuAt (mcwMenu w) x of Nothing -> pure True Just (SubMenu smi) -> do modifyWRef ref (\w' -> w' { mcwMenu = (mcwMenu w) { menuActive = Just (x, Prelude.length smi - 1) }}) pure True (KeyCtrl _ _ _ ArrowDown, Just (x, y)) -> do case getSubmenuAt (mcwMenu w) x of Just (SubMenu smi) -> do let newY = y + 1 if newY < (Prelude.length smi) then do modifyWRef ref (\w' -> w' { mcwMenu = (mcwMenu w) { menuActive = Just (x, newY) }}) pure True else do modifyWRef ref (\w' -> w' { mcwMenu = (mcwMenu w) { menuActive = Just (x, 0) }}) pure True Nothing -> pure True (KeyCtrl _ _ _ Return, Just (x, y)) -> do (mcwSelectionHandler w) ref (x, y) setCursorVisibility True pure True _ -> pure False scopeToWatchItems :: Scope -> [(Text, Text)] scopeToWatchItems s = Map.foldlWithKey' (\o k v -> let vKey = case k of SkIdentifier i -> unIdentifer i SkOperator op -> T.pack $ show op vText = case v of StringValue t -> Just t NumberValue (NumberInt t) -> Just $ T.pack $ show t NumberValue (NumberFractional t) -> Just $ T.pack $ show t BoolValue t -> Just $ T.pack $ show t ArrayValue t -> Just $ T.pack $ show t ObjectValue t -> Just $ T.pack $ show t _ -> Nothing in case vText of Just t -> (vKey, t) : o Nothing -> o ) [] s selectionHandler :: forall m. WidgetC m => TChan IDEEvent -> WRef MenuContainerWidget -> (Int, Int) -> m () selectionHandler ideEventsRef ref selection = do case selection of (0, 0) -> liftIO $ atomically $ writeTChan ideEventsRef IDESave (0, 1) -> liftIO $ atomically $ writeTChan ideEventsRef IDEBeautify (0, 2) -> liftIO $ atomically $ writeTChan ideEventsRef IDEExit (1, 0) -> liftIO $ atomically $ writeTChan ideEventsRef (IDEEdit Cut) (1, 1) -> liftIO $ atomically $ writeTChan ideEventsRef (IDEEdit Copy) (1, 2) -> liftIO $ atomically $ writeTChan ideEventsRef (IDEEdit Paste) (1, 3) -> liftIO $ atomically $ writeTChan ideEventsRef (IDEEdit SelectAll) (2, 0) -> liftIO $ atomically $ writeTChan ideEventsRef IDERun (2, 1) -> liftIO $ atomically $ writeTChan ideEventsRef IDEStep (3, 0) -> liftIO $ atomically $ writeTChan ideEventsRef IDEClearLog (4, 0) -> liftIO $ atomically $ writeTChan ideEventsRef IDEToggleHelp _ -> pass modifyWRef ref (\mcw -> mcw { mcwMenu = (mcwMenu mcw) { menuActive = Nothing } }) liftIO $ atomically $ writeTChan ideEventsRef IDEDraw shortcutsHandler :: forall m. WidgetC m => TChan IDEEvent -> KeyEvent -> m Bool shortcutsHandler ideEventRef kv = do case kv of KeyCtrl _ _ _ (Fun 6) -> do liftIO $ atomically $ writeTChan ideEventRef IDESave pure True KeyCtrl _ _ _ (Fun 1) -> do liftIO $ atomically $ writeTChan ideEventRef IDEToggleHelp pure True KeyCtrl True _ _ (Fun 8) -> do liftIO $ atomically $ writeTChan ideEventRef IDEStep pure True KeyCtrl _ _ _ (Fun 5) -> do liftIO $ atomically $ writeTChan ideEventRef IDERun pure True _ -> pure False