Skip to content

Commit fe6e750

Browse files
Restyled by fourmolu
1 parent cdb0938 commit fe6e750

File tree

8 files changed

+47
-44
lines changed

8 files changed

+47
-44
lines changed

src/swarm-lang/Swarm/Language/LSP.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -22,9 +22,9 @@ import Language.LSP.Protocol.Types qualified as LSP
2222
import Language.LSP.Server
2323
import Language.LSP.VFS (VirtualFile (..), virtualFileText)
2424
import Swarm.Failure (SystemFailure (..))
25-
import Swarm.Language.Load (SyntaxWithImports (..))
2625
import Swarm.Language.LSP.Hover qualified as H
2726
import Swarm.Language.LSP.VarUsage qualified as VU
27+
import Swarm.Language.Load (SyntaxWithImports (..))
2828
import Swarm.Language.Parser.Util (getLocRange)
2929
import Swarm.Language.Pipeline (processSource)
3030
import Swarm.Language.Syntax (SrcLoc (..), eraseRaw)

src/swarm-lang/Swarm/Language/Load.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,7 @@ import Swarm.Language.Parser.Core (defaultParserConfig, importLoc)
3535
import Swarm.Language.Syntax (ImportPhaseFor, Phase (..), SwarmType, Syntax)
3636
import Swarm.Language.Syntax.Import hiding (ImportPhase (..))
3737
import Swarm.Language.Syntax.Import qualified as Import
38-
import Swarm.Language.Syntax.Util (Erasable(..), traverseSyntax)
38+
import Swarm.Language.Syntax.Util (Erasable (..), traverseSyntax)
3939
import Swarm.Language.Types (TCtx, UCtx)
4040
import Swarm.Util (readFileMayT, showT)
4141
import Swarm.Util.Graph (findCycle)
@@ -211,7 +211,6 @@ readLoc loc = do
211211

212212
-- Try to read the file from network/disk, depending on the anchor
213213
src <- case importAnchor loc of
214-
215214
-- Read from network
216215
Web_ {} -> do
217216
-- Try to parse the URL

src/swarm-lang/Swarm/Language/Parser/Value.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -51,8 +51,9 @@ readValue ty txt = do
5151
-- encountered; we can't read those anyway.
5252
sResolved <- eitherToMaybe . run . runError @SystemFailure $ resolve' s
5353
-- Now, make sure the resolved term typechecks at the given type.
54-
_ <- eitherToMaybe . runError @ContextualTypeErr $
55-
checkTop Ctx.empty Ctx.empty emptyTDCtx M.empty sResolved ty
54+
_ <-
55+
eitherToMaybe . runError @ContextualTypeErr $
56+
checkTop Ctx.empty Ctx.empty emptyTDCtx M.empty sResolved ty
5657
-- Finally, turn the term into a value.
5758
toValue $ s ^. sTerm
5859

src/swarm-lang/Swarm/Language/Typecheck.hs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -885,19 +885,19 @@ inferTop ::
885885
Has (Error ContextualTypeErr) sig m =>
886886
TCtx -> ReqCtx -> TDCtx -> SourceMap Resolved -> Syntax Resolved -> m (SyntaxWithImports Typed)
887887
inferTop ctx reqCtx tdCtx srcMap =
888-
fmap (uncurry SyntaxWithImports) .
889-
runTC ctx reqCtx tdCtx Ctx.empty srcMap .
890-
infer
888+
fmap (uncurry SyntaxWithImports)
889+
. runTC ctx reqCtx tdCtx Ctx.empty srcMap
890+
. infer
891891

892892
-- | Top level type checking function.
893893
checkTop ::
894894
Has (Error ContextualTypeErr) sig m =>
895895
TCtx -> ReqCtx -> TDCtx -> SourceMap Resolved -> Syntax Resolved -> Type -> m (SyntaxWithImports Typed)
896896
checkTop ctx reqCtx tdCtx srcMap t =
897-
fmap (uncurry SyntaxWithImports) .
898-
runTC ctx reqCtx tdCtx Ctx.empty srcMap .
899-
check t .
900-
toU
897+
fmap (uncurry SyntaxWithImports)
898+
. runTC ctx reqCtx tdCtx Ctx.empty srcMap
899+
. check t
900+
. toU
901901

902902
-- | Infer the type of a term, returning a type-annotated term.
903903
--

src/swarm-lang/Swarm/Language/Value.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -178,7 +178,7 @@ makeLenses ''Env
178178

179179
-- | Create an environment which is empty except for an initial SourceMap.
180180
envFromSrcMap :: SourceMap Elaborated -> Env
181-
envFromSrcMap srcMap = emptyEnv { _envSourceMap = srcMap }
181+
envFromSrcMap srcMap = emptyEnv {_envSourceMap = srcMap}
182182

183183
emptyEnv :: Env
184184
emptyEnv = Env Ctx.empty Ctx.empty Ctx.empty emptyTDCtx M.empty

src/swarm-tui/Swarm/TUI/Controller.hs

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -890,7 +890,7 @@ validateREPLForm s =
890890
(theType, errSrcLoc) = case readTerm' defaultParserConfig uinput of
891891
Left err ->
892892
let (((_y1, x1), (_y2, x2)), _msg) = showErrorPos err
893-
in (Nothing, Left (SrcLoc Nothing x1 x2))
893+
in (Nothing, Left (SrcLoc Nothing x1 x2))
894894
Right Nothing -> (Nothing, Right ())
895895
Right (Just theTerm) ->
896896
-- Explicitly ignore REPL entries with imports,
@@ -899,15 +899,15 @@ validateREPLForm s =
899899
-- be properly resolved and checked when the
900900
-- user hits enter.
901901
let res = run . runError @SystemFailure $ processTermNoImports uinput theTerm (Just env)
902-
in case res of
903-
Right t -> (Just (t ^. sType), Right ())
904-
Left (DoesNotTypecheck loc _) -> (Nothing, Left loc)
905-
-- Don't signal an error if the REPL entry contained an import
906-
Left (DisallowedImport _) -> (Nothing, Right ())
907-
_ -> (Nothing, Right ())
902+
in case res of
903+
Right t -> (Just (t ^. sType), Right ())
904+
Left (DoesNotTypecheck loc _) -> (Nothing, Left loc)
905+
-- Don't signal an error if the REPL entry contained an import
906+
Left (DisallowedImport _) -> (Nothing, Right ())
907+
_ -> (Nothing, Right ())
908908
in s
909-
& uiGameplay . uiREPL . replValid .~ errSrcLoc
910-
& uiGameplay . uiREPL . replType .~ theType
909+
& uiGameplay . uiREPL . replValid .~ errSrcLoc
910+
& uiGameplay . uiREPL . replType .~ theType
911911
SearchPrompt _ -> s
912912
where
913913
uinput = s ^. uiGameplay . uiREPL . replPromptText

test/unit/TestLanguagePipeline.hs

Lines changed: 17 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -17,8 +17,8 @@ import Data.Text (Text)
1717
import Data.Text qualified as T
1818
import Data.Text.Encoding qualified as T
1919
import Swarm.Failure (SystemFailure)
20-
import Swarm.Language.Load (SyntaxWithImports (..))
2120
import Swarm.Language.JSON ()
21+
import Swarm.Language.Load (SyntaxWithImports (..))
2222
import Swarm.Language.Parser (readTerm)
2323
import Swarm.Language.Parser.QQ (tyQ)
2424
import Swarm.Language.Pipeline (processSource)
@@ -766,22 +766,22 @@ testLanguagePipeline =
766766
"Import #2540"
767767
[ testCase
768768
"simple import"
769-
( valid "import \"data/test/import/a.sw\"; pure (a + 1)" )
769+
(valid "import \"data/test/import/a.sw\"; pure (a + 1)")
770770
, testCase
771771
"recursive import - unused"
772-
( valid "import \"data/test/import/b.sw\"; pure (b + 1)" )
772+
(valid "import \"data/test/import/b.sw\"; pure (b + 1)")
773773
, testCase
774774
"recursive import - used"
775-
( valid "import \"data/test/import/d.sw\"; pure (d + 1)" )
775+
(valid "import \"data/test/import/d.sw\"; pure (d + 1)")
776776
, testCase
777777
"recursive import is not re-exported"
778778
( process
779-
"import \"data/test/import/f.sw\"; pure (f + g)"
780-
"1:43: Unbound variable g"
779+
"import \"data/test/import/f.sw\"; pure (f + g)"
780+
"1:43: Unbound variable g"
781781
)
782782
, testCase
783783
"import from URL"
784-
( valid "import \"https://raw.githubusercontent.com/byorgey/swarm-defs/refs/heads/main/defs.sw\"; tL")
784+
(valid "import \"https://raw.githubusercontent.com/byorgey/swarm-defs/refs/heads/main/defs.sw\"; tL")
785785
]
786786
]
787787
where
@@ -791,15 +791,16 @@ testLanguagePipeline =
791791
process = processCompare T.isPrefixOf
792792

793793
processCompare :: (Text -> Text -> Bool) -> Text -> Text -> Assertion
794-
processCompare cmp code expect = runError @SystemFailure (processSource code Nothing) >>= \case
795-
Left e
796-
| not (T.null expect) && cmp expect (prettyText e) -> pure ()
797-
| otherwise ->
798-
error $
799-
"Unexpected failure:\n\n " <> show (prettyText e) <> "\n\nExpected:\n\n " <> show expect <> "\n"
800-
Right _
801-
| expect == "" -> pure ()
802-
| otherwise -> error "Unexpected success"
794+
processCompare cmp code expect =
795+
runError @SystemFailure (processSource code Nothing) >>= \case
796+
Left e
797+
| not (T.null expect) && cmp expect (prettyText e) -> pure ()
798+
| otherwise ->
799+
error $
800+
"Unexpected failure:\n\n " <> show (prettyText e) <> "\n\nExpected:\n\n " <> show expect <> "\n"
801+
Right _
802+
| expect == "" -> pure ()
803+
| otherwise -> error "Unexpected success"
803804

804805
-- | Check round tripping of term from and to text, then test ToJSON/FromJSON.
805806
roundTripTerm :: Text -> Assertion

test/unit/TestUtil.hs

Lines changed: 8 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@ module TestUtil where
99

1010
import Control.Carrier.Error.Either (runError)
1111
import Control.Lens (Ixed (ix), to, use, (&), (.~), (^.), (^?))
12-
import Control.Monad ((<=<), void)
12+
import Control.Monad (void, (<=<))
1313
import Control.Monad.State (StateT (..), execState)
1414
import Control.Monad.Trans (lift)
1515
import Data.Bifunctor (first)
@@ -37,8 +37,9 @@ eval :: GameState -> Text -> IO (GameState, Robot Instantiated, Either Text (Val
3737
eval g = either (return . (g,hypotheticalRobot undefined 0,) . Left) (evalPT g) <=< processTerm1
3838

3939
processTerm1 :: Text -> IO (Either Text (SyntaxWithImports Elaborated))
40-
processTerm1 txt = fmap (first prettyText) . runError @SystemFailure $
41-
processSource txt Nothing >>= requireNonEmptyTerm
40+
processTerm1 txt =
41+
fmap (first prettyText) . runError @SystemFailure $
42+
processSource txt Nothing >>= requireNonEmptyTerm
4243

4344
evalPT :: GameState -> SyntaxWithImports Elaborated -> IO (GameState, Robot Instantiated, Either Text (Value, Int))
4445
evalPT g t = evalCESK g (initMachine t)
@@ -84,6 +85,7 @@ playUntilDone rid = do
8485
Nothing -> return $ Left . T.pack $ "The robot with ID " <> show rid <> " is nowhere to be found!"
8586

8687
check :: Text -> (SyntaxWithImports Elaborated -> Bool) -> Assertion
87-
check code expect = processTerm1 code >>= \case
88-
Left err -> assertFailure $ "Term processing failed: " ++ into @String err
89-
Right t -> assertBool "Predicate was false!" (expect t)
88+
check code expect =
89+
processTerm1 code >>= \case
90+
Left err -> assertFailure $ "Term processing failed: " ++ into @String err
91+
Right t -> assertBool "Predicate was false!" (expect t)

0 commit comments

Comments
 (0)