Skip to content

Commit

Permalink
Restyled by fourmolu (#1958)
Browse files Browse the repository at this point in the history
Co-authored-by: Restyled.io <[email protected]>
  • Loading branch information
restyled-io[bot] and restyled-commits authored Jun 18, 2024
1 parent 7ae5e75 commit d5307f9
Show file tree
Hide file tree
Showing 3 changed files with 18 additions and 18 deletions.
19 changes: 9 additions & 10 deletions src/swarm-tui/Swarm/TUI/Controller.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}

{-# HLINT ignore "Use fewer imports" #-}

-- |
Expand Down Expand Up @@ -41,9 +42,6 @@ module Swarm.TUI.Controller (

import Brick hiding (Direction, Location)
import Brick.Focus
import Swarm.Language.Parser (readTerm')
import Swarm.Language.Parser.Util (showErrorPos)
import Swarm.Language.Parser.Core (defaultParserConfig)
import Brick.Widgets.Dialog
import Brick.Widgets.Edit (applyEdit, handleEditorEvent)
import Brick.Widgets.List (handleListEvent)
Expand Down Expand Up @@ -97,18 +95,19 @@ import Swarm.Game.State.Runtime
import Swarm.Game.State.Substate
import Swarm.Game.Step (finishGameTick, gameTick)
import Swarm.Language.Capability (Capability (CGod, CMake), constCaps)
import Swarm.Language.Typecheck (ContextualTypeErr(..))
import Swarm.Language.Capability (Capability (CGod), constCaps)
import Swarm.Language.Context
import Swarm.Language.Key (KeyCombo, mkKeyCombo)
import Swarm.Language.Module (moduleSyntax)
import Swarm.Language.Parser (readTerm')
import Swarm.Language.Parser.Core (defaultParserConfig)
import Swarm.Language.Parser.Lex (reservedWords)
import Swarm.Language.Pipeline (Contexts (..), ProcessedTerm (..), processTerm', processedSyntax)
import Swarm.Language.Pipeline (processTerm', processParsedTerm')
import Swarm.Language.Parser.Util (showErrorPos)
import Swarm.Language.Pipeline (Contexts (..), ProcessedTerm (..), processParsedTerm', processTerm', processedSyntax)
import Swarm.Language.Pipeline.QQ (tmQ)
import Swarm.Language.Pretty
import Swarm.Language.Requirement qualified as R
import Swarm.Language.Syntax hiding (Key)
import Swarm.Language.Typecheck (ContextualTypeErr (..))
import Swarm.Language.Typed (Typed (..))
import Swarm.Language.Types
import Swarm.Language.Value (Value (VExc, VKey, VUnit), prettyValue, stripVResult)
Expand Down Expand Up @@ -1309,15 +1308,15 @@ validateREPLForm s =
in s & uiState . uiGameplay . uiREPL . replType .~ theType
CmdPrompt _
| otherwise ->
let ctxs = Contexts (topCtx ^. defTypes) (topCtx ^. defReqs) (topCtx ^. tydefVals)
let ctxs = Contexts (topCtx ^. defTypes) (topCtx ^. defReqs) (topCtx ^. tydefVals)
(theType, errSrcLoc) = case readTerm' defaultParserConfig uinput of
Left err ->
Left err ->
let ((x1, _y1), (x2, _y2), _msg) = showErrorPos err
in (Nothing, SrcLoc x1 x2)
Right Nothing -> (Nothing, NoLoc)
Right (Just theTerm) -> case processParsedTerm' ctxs theTerm of
Right t -> (Just (t ^. processedSyntax . sType), NoLoc)
Left err -> (Nothing, cteSrcLoc err)
Left err -> (Nothing, cteSrcLoc err)
in s
& uiState . uiGameplay . uiREPL . replValid .~ isJust theType
& uiState . uiGameplay . uiREPL . replType .~ theType
Expand Down
3 changes: 1 addition & 2 deletions src/swarm-tui/Swarm/TUI/Model/Repl.hs
Original file line number Diff line number Diff line change
Expand Up @@ -64,12 +64,11 @@ import Data.Text qualified as T
import Data.Text.Zipper qualified as TZ
import Servant.Docs (ToSample)
import Servant.Docs qualified as SD
import Swarm.Language.Syntax (SrcLoc (..))
import Swarm.Language.Types
import Swarm.TUI.Model.Name
import Swarm.Util.Lens (makeLensesNoSigs)
import Prelude hiding (Applicative (..))
import Swarm.Language.Syntax (SrcLoc)
import Swarm.Language.Syntax (SrcLoc(..))

------------------------------------------------------------
-- REPL History
Expand Down
14 changes: 8 additions & 6 deletions src/swarm-tui/Swarm/TUI/View.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1540,12 +1540,14 @@ renderREPLPrompt focus theRepl = ps1 <+> replE
where
prompt = theRepl ^. replPromptType
replEditor = theRepl ^. replPromptEditor
color t = if theRepl ^. replValid
then txt t
else case theRepl ^. replErrorSrcLoc of
NoLoc -> withAttr redAttr (txt t)
SrcLoc s e -> let (validL, (invalid, validR)) = T.splitAt e <$> T.splitAt s t
in hBox [txt validL, withAttr redAttr (txt invalid), txt validR]
color t =
if theRepl ^. replValid
then txt t
else case theRepl ^. replErrorSrcLoc of
NoLoc -> withAttr redAttr (txt t)
SrcLoc s e ->
let (validL, (invalid, validR)) = T.splitAt e <$> T.splitAt s t
in hBox [txt validL, withAttr redAttr (txt invalid), txt validR]
ps1 = replPromptAsWidget (T.concat $ getEditContents replEditor) prompt
replE =
renderEditor
Expand Down

0 comments on commit d5307f9

Please sign in to comment.