diff --git a/README.md b/README.md
index b347e51..be9de38 100644
--- a/README.md
+++ b/README.md
@@ -76,7 +76,6 @@ stack_snapshot(
     name = "stackage",
     packages = [
         "aeson",
-        "parsec",
     ],
     # Most snapshots of your choice might do
     snapshot = "lts-18.1",
diff --git a/WORKSPACE b/WORKSPACE
index a7e90f5..aede37a 100644
--- a/WORKSPACE
+++ b/WORKSPACE
@@ -51,7 +51,6 @@ stack_snapshot(
     packages = [
         "aeson",
         "hspec",
-        "parsec",
         "string-qq",
         "tasty",
         "tasty-discover",
diff --git a/defs.bzl b/defs.bzl
index d4add5b..5f2857e 100644
--- a/defs.bzl
+++ b/defs.bzl
@@ -7,10 +7,8 @@ def _gazelle_haskell_modules_dependencies_impl(repository_ctx):
 package(default_visibility = ["//visibility:public"])
 
 alias(name="aeson", actual="{aeson}")
-alias(name="parsec", actual="{parsec}")
         '''.format(
             aeson = repository_ctx.attr.aeson,
-            parsec = repository_ctx.attr.parsec,
         ),
         executable = False,
     )
@@ -20,7 +18,6 @@ _gazelle_haskell_modules_dependencies = repository_rule(
     local = True,
     attrs = {
         "aeson": attr.label(default = "@stackage//:aeson"),
-        "parsec": attr.label(default = "@stackage//:parsec"),
     },
 )
 
@@ -41,7 +38,6 @@ def gazelle_haskell_modules_dependencies(**kargs):
       # Dependencies overriden
       gazelle_haskell_modules_dependencies(
           aeson = "@someother//:some-other-aeson",
-          parsec = "@someother//:parsec",
       )
 
       ```
diff --git a/example/WORKSPACE b/example/WORKSPACE
index 7d7cd99..3c6c110 100644
--- a/example/WORKSPACE
+++ b/example/WORKSPACE
@@ -56,8 +56,8 @@ stack_snapshot(
     packages = [
         "aeson",
         "base",
+        "ghc-paths",
         "inspection-testing",
-        "parsec",
         "tasty",
         "tasty-discover",
         "tasty-hunit",
diff --git a/example/package-a/app/Main.hs b/example/package-a/app/Main.hs
index e67c5e7..6b0c84a 100644
--- a/example/package-a/app/Main.hs
+++ b/example/package-a/app/Main.hs
@@ -1,10 +1,20 @@
 {-# LANGUAGE CPP #-}
+{-# LANGUAGE PatternSynonyms #-}
+{-# LANGUAGE ExplicitNamespaces #-}
+{-# LANGUAGE MagicHash #-}
 module Main where
 
 #define a_multiline macro \
   a second line of the macro
 import NonModulesLib (nonModulesLib)
-import PackageA.Other.C()
+import PackageA.Other.C(type DataC, DataC(DataC), pattern PatTrue)
+import GHC.Exts (Int(..), Int#)
 
 main :: IO ()
-main = putStrLn $ "Hello, Haskell! " ++ show nonModulesLib
+main = do
+  let
+    dataC :: DataC
+    dataC = DataC PatTrue
+    int# :: Int#
+    int# = case 1 of I# i -> i
+  putStrLn $ "Hello, Haskell! " ++ show nonModulesLib ++ show dataC ++ show (I# int#)
diff --git a/example/package-a/app/PackageA/Other/C.hs b/example/package-a/app/PackageA/Other/C.hs
index 31d08fc..da3de48 100644
--- a/example/package-a/app/PackageA/Other/C.hs
+++ b/example/package-a/app/PackageA/Other/C.hs
@@ -1,3 +1,10 @@
+{-# LANGUAGE PatternSynonyms #-}
 module PackageA.Other.C where
 
 import PackageA.Exposed.A()
+
+data DataC = DataC Bool
+  deriving Show
+
+pattern PatTrue :: Bool
+pattern PatTrue = True
diff --git a/gazelle_haskell_modules/rule_generation.go b/gazelle_haskell_modules/rule_generation.go
index 0c7ba4d..f4e8741 100644
--- a/gazelle_haskell_modules/rule_generation.go
+++ b/gazelle_haskell_modules/rule_generation.go
@@ -1,6 +1,7 @@
 package gazelle_haskell_modules
 
 import (
+	"bytes"
 	"encoding/json"
 	"fmt"
 	"io/fs"
@@ -151,15 +152,37 @@ func haskellModulesToModuleData(moduleFiles []string) []*ModuleData {
 	cmd := exec.Command(himportscan)
 
 	cmd.Stdin = strings.NewReader(strings.Join(moduleFiles, "\n"))
-	out, err := cmd.CombinedOutput()
+
+	var stdout bytes.Buffer
+	cmd.Stdout = &stdout
+
+	var stderr strings.Builder
+	cmd.Stderr = &stderr
+
+	err = cmd.Start()
 	if err != nil {
-		log.Printf("%s", out)
-		log.Fatal(err)
+		log.Fatalf("himportscan failed to start %v", err)
 	}
+
+	err = cmd.Wait()
+	stdoutBytes := stdout.Bytes()
+	stderrString := stderr.String()
+
+	if err != nil {
+		fmt.Printf("%s\n", stdout.Bytes())
+		fmt.Printf("%s\n", stderrString)
+		log.Fatalf("himportscan exited unsuccessfully %v\n", err)
+	}
+
+	// print stderr so if himportscan generates some stderr but doesn't fail the user might see useful output
+	if stderrString != "" {
+		log.Printf("%s\n", stderrString)
+	}
+
 	var modDatas []*ModuleData
-	err = json.Unmarshal(out, &modDatas)
+	err = json.Unmarshal(stdoutBytes, &modDatas)
 	if err != nil {
-		log.Printf("Incorrect json: %s\n", out)
+		log.Printf("Incorrect json: %s\n", stdoutBytes)
 		log.Fatal(err)
 	}
 	return modDatas
diff --git a/himportscan/BUILD.bazel b/himportscan/BUILD.bazel
index f18ec3c..d6080f5 100644
--- a/himportscan/BUILD.bazel
+++ b/himportscan/BUILD.bazel
@@ -12,10 +12,16 @@ haskell_toolchain_library(name = "base")
 
 haskell_toolchain_library(name = "bytestring")
 
+haskell_toolchain_library(name = "containers")
+
 haskell_toolchain_library(name = "directory")
 
 haskell_toolchain_library(name = "ghc")
 
+# Needed for GHC.LanguageExtensions.
+# You can probably revisit this when changing ghc versions.
+haskell_toolchain_library(name = "ghc-boot")
+
 haskell_toolchain_library(name = "text")
 
 haskell_library(
@@ -28,11 +34,12 @@ haskell_library(
     deps = [
         ":base",
         ":bytestring",
+        ":containers",
         ":directory",
         ":ghc",
+        ":ghc-boot",
         ":text",
         "@io_tweag_gazelle_haskell_modules_deps//:aeson",
-        "@io_tweag_gazelle_haskell_modules_deps//:parsec",
     ],
 )
 
@@ -46,6 +53,7 @@ haskell_binary(
     deps = [
         ":base",
         ":bytestring",
+        ":containers",
         ":ghc",
         ":himportscan-library",
         ":text",
@@ -66,6 +74,7 @@ haskell_test(
     ],
     deps = [
         ":base",
+        ":containers",
         ":himportscan-library",
         ":text",
         "@stackage//:hspec",
diff --git a/himportscan/exe/Main.hs b/himportscan/exe/Main.hs
index 9ffc78d..82ee57c 100644
--- a/himportscan/exe/Main.hs
+++ b/himportscan/exe/Main.hs
@@ -2,10 +2,10 @@
 {-# LANGUAGE OverloadedStrings #-}
 module Main where
 
-import HImportScan.ImportScanner (ScannedImports, scanImportsFromFile)
 import qualified Data.Aeson as Aeson
 import qualified Data.ByteString.Lazy.Char8 as ByteString.Lazy
 import Data.Maybe (catMaybes)
+import HImportScan.ImportScanner (ScannedImports, scanImportsFromFile)
 
 main :: IO ()
 main = do
diff --git a/himportscan/src/HImportScan/GHC.hs b/himportscan/src/HImportScan/GHC.hs
index a296c14..ab3d77e 100644
--- a/himportscan/src/HImportScan/GHC.hs
+++ b/himportscan/src/HImportScan/GHC.hs
@@ -1,8 +1,24 @@
 -- | A module abstracting the provenance of GHC API names
 module HImportScan.GHC(module X) where
 
+import DynFlags as X (DynFlags, defaultDynFlags, xopt_set, xopt_unset)
 import EnumSet as X (empty, fromList)
-import FastString as X (mkFastString, unpackFS)
+import ErrUtils as X (printBagOfErrors)
+import FastString as X (FastString, mkFastString, bytesFS)
+import GHC as X (runGhc, getSessionDynFlags)
+import GHC.LanguageExtensions as X
+  (Extension
+    ( ImportQualifiedPost
+    , PackageImports
+    , TemplateHaskell
+    , ImplicitPrelude
+    , PatternSynonyms
+    , ExplicitNamespaces
+    , MagicHash
+    )
+  )
+import HeaderInfo as X (getOptions, getImports)
+import HscTypes as X (mkSrcErr)
 import Lexer as X
   ( ParseResult(..)
   , Token(..)
@@ -11,6 +27,7 @@ import Lexer as X
   , mkParserFlags'
   , mkPStatePure, unP
   )
+import Module as X (ModuleName, moduleNameString)
 import SrcLoc as X
   ( Located
   , RealSrcLoc
@@ -22,4 +39,4 @@ import SrcLoc as X
   , srcSpanStart
   , unLoc
   )
-import StringBuffer as X (StringBuffer(StringBuffer))
+import StringBuffer as X (StringBuffer(StringBuffer), stringToStringBuffer)
diff --git a/himportscan/src/HImportScan/GHC/Settings.hs b/himportscan/src/HImportScan/GHC/Settings.hs
new file mode 100644
index 0000000..27ca70a
--- /dev/null
+++ b/himportscan/src/HImportScan/GHC/Settings.hs
@@ -0,0 +1,50 @@
+-- Copyright (c) 2020, Shayne Fletcher. All rights reserved.
+-- SPDX-License-Identifier: BSD-3-Clause.
+
+{-# OPTIONS_GHC -Wno-missing-fields #-}
+{-# OPTIONS_GHC -Wno-name-shadowing #-}
+
+-- This file is a single code path copied over from https://hackage.haskell.org/package/ghc-lib-parser-ex-8.10.0.24/docs/src/Language.Haskell.GhclibParserEx.GHC.Settings.Config.html
+-- TODO[GL]: We can get rid of this file once we only support >=9.2, as ParserOpts are much smaller there.
+module HImportScan.GHC.Settings(
+    fakeSettings
+  , fakeLlvmConfig
+  )
+where
+
+import Config
+import DynFlags
+import Fingerprint
+import GHC.Platform
+import ToolSettings
+
+fakeSettings :: Settings
+fakeSettings = Settings
+  { sGhcNameVersion=ghcNameVersion
+  , sFileSettings=fileSettings
+  , sTargetPlatform=platform
+  , sPlatformMisc=platformMisc
+  , sPlatformConstants=platformConstants
+  , sToolSettings=toolSettings
+  }
+  where
+    toolSettings = ToolSettings {
+      toolSettings_opt_P_fingerprint=fingerprint0
+      }
+    fileSettings = FileSettings {}
+    platformMisc = PlatformMisc {}
+    ghcNameVersion =
+      GhcNameVersion{ghcNameVersion_programName="ghc"
+                    ,ghcNameVersion_projectVersion=cProjectVersion
+                    }
+    platform =
+      Platform{
+        platformWordSize=PW8
+      , platformMini=PlatformMini {platformMini_arch=ArchUnknown, platformMini_os=OSUnknown}
+      , platformUnregisterised=True
+      }
+    platformConstants =
+      PlatformConstants{pc_DYNAMIC_BY_DEFAULT=False,pc_WORD_SIZE=8}
+
+fakeLlvmConfig :: LlvmConfig
+fakeLlvmConfig = LlvmConfig [] []
diff --git a/himportscan/src/HImportScan/ImportScanner.hs b/himportscan/src/HImportScan/ImportScanner.hs
index 0d63c72..f932214 100644
--- a/himportscan/src/HImportScan/ImportScanner.hs
+++ b/himportscan/src/HImportScan/ImportScanner.hs
@@ -16,26 +16,27 @@ module HImportScan.ImportScanner
   , scanImportsFromFile
   ) where
 
+import Data.ByteString.Internal(ByteString(PS))
+import Control.Exception (throwIO)
 import qualified Data.Aeson as Aeson
-import Data.ByteString.Internal(ByteString(..))
-import Data.Char (isAlphaNum, isSpace, toLower)
-import Data.List (isSuffixOf, nub)
+import Data.Char (toLower)
+import Data.List (isSuffixOf)
 import Data.Maybe (catMaybes)
+import Data.Set (Set)
+import qualified Data.Set as Set
 import Data.Text (Text)
 import qualified Data.Text as Text
-import qualified Data.Text.IO as Text
 import qualified Data.Text.Encoding as Text
+import qualified Data.Text.IO as Text
 import HImportScan.GHC as GHC
+import qualified HImportScan.GHC.Settings as GHC.Settings
 import System.Directory (doesFileExist)
-import Text.Parsec hiding (satisfy)
-import Text.Parsec.Pos (newPos)
-
 
 -- | Holds the names of modules imported in a Haskell module.
 data ScannedImports = ScannedImports
   { filePath :: Text  -- ^ Path of the Haskell module
   , moduleName :: Text  -- ^ The module name
-  , importedModules :: [ModuleImport] -- ^ The modules imported in this module
+  , importedModules :: Set ModuleImport -- ^ The modules imported in this module
   , usesTH :: Bool  -- ^ Whether the module needs TH or the interpreter
   }
   deriving Eq
@@ -43,7 +44,7 @@ data ScannedImports = ScannedImports
 -- | A module import holds a module name and an optional package name
 -- when using package imports.
 data ModuleImport = ModuleImport (Maybe Text) Text
-  deriving Eq
+  deriving (Eq, Ord)
 
 instance Aeson.ToJSON ScannedImports where
   toJSON (ScannedImports filePath moduleName importedModules usesTH) =
@@ -68,28 +69,69 @@ scanImportsFromFile :: FilePath -> IO (Maybe ScannedImports)
 scanImportsFromFile filePath = do
   fileExists <- doesFileExist filePath
   if fileExists
-  then Just . scanImports filePath <$> Text.readFile filePath
+  then fmap Just . scanImports filePath =<< Text.readFile filePath
   else pure Nothing
 
-scanImports :: FilePath -> Text -> ScannedImports
-scanImports filePath contents =
-  let preprocessedContents = Text.encodeUtf8 $ preprocessContents contents
-      sbuffer = case preprocessedContents of
+-- TODO[GL]: This function is only in IO because
+-- * we use printBagOfErrors to report an error, but we can easily factor that out
+-- * getImports is in IO, which in turn is only in IO to throw an error
+--   Perhaps we could raise an issue at ghc to make a pure variant.
+scanImports :: FilePath -> Text -> IO ScannedImports
+scanImports filePath contents = do
+  let sb = case Text.encodeUtf8 $ preprocessContents contents of
         PS ptr offset len -> StringBuffer ptr len offset
-      loc = mkRealSrcLoc (mkFastString filePath) 1 1
-   in case scanTokenStream filePath $ lexTokenStream sbuffer loc of
-    Left err -> error err
-    Right ScannedData{moduleName, importedModules, usesTH} ->
-      ScannedImports
-        { filePath = Text.pack filePath
-        , moduleName
-        , importedModules
-        , usesTH
-        }
 
+  -- TODO[GL]: Once we're on ghc 9.2 we can get rid of all the things relating to dynFlags, and use the much smaller
+  -- ParserOpts, as getImports no longer depends on DynFlags then.
+  let dynFlagsWithExtensions = toggleDynFlags $ GHC.defaultDynFlags GHC.Settings.fakeSettings GHC.Settings.fakeLlvmConfig
+
+  let
+    -- [GL] The fact that the resulting strings here contain the "-X"s makes me a bit doubtful that this is the right approach,
+    -- but this is what I found for now.
+    usesTH =
+      any (`elem` ["-XTemplateHaskell", "-XQuasiQuotes"]) $
+        map GHC.unLoc $
+          GHC.getOptions dynFlagsWithExtensions sb filePath
+  GHC.getImports dynFlagsWithExtensions sb filePath filePath >>= \case
+    -- It's important that we error in this case to signal to the user that
+    -- something needs fixing in the source file.
+    Left err -> do
+      GHC.printBagOfErrors dynFlagsWithExtensions err
+      throwIO (GHC.mkSrcErr err)
+    Right (sourceImports, normalImports, moduleName) -> do
+      pure ScannedImports
+            { filePath = Text.pack filePath
+            , moduleName = moduleNameToText moduleName
+            , importedModules =
+                let
+                  toModuleImport :: (Maybe GHC.FastString, GHC.Located GHC.ModuleName) -> ModuleImport
+                  toModuleImport (mfs, locatedModuleName) =
+                    ModuleImport
+                      (fmap (Text.decodeUtf8 . GHC.bytesFS) mfs)
+                      (moduleNameToText locatedModuleName)
+                 in Set.fromList $ map toModuleImport $ sourceImports ++ normalImports
+            , usesTH
+            }
   where
     preprocessContents = Text.unlines . flipBirdTracks filePath . clearCPPDirectives . Text.lines
 
+    moduleNameToText = Text.pack . GHC.moduleNameString . GHC.unLoc
+
+-- Toggle extensions to the state we want them in.
+-- We should handle all forms of imports.
+-- We turn off ImplicitPrelude, because otherwise it shows up in imports lists which ghc returns.
+toggleDynFlags :: GHC.DynFlags -> GHC.DynFlags
+toggleDynFlags dflags0 =
+  let dflags1 = foldl GHC.xopt_set dflags0
+                  [ GHC.ImportQualifiedPost
+                  , GHC.PackageImports
+                  , GHC.TemplateHaskell
+                  , GHC.PatternSynonyms
+                  , GHC.ExplicitNamespaces
+                  , GHC.MagicHash
+                  ]
+   in GHC.xopt_unset dflags1 GHC.ImplicitPrelude
+
 -- | Clear CPP directives since they would otherwise confuse the scanner.
 --
 -- Takes as inputs the contents of a Haskell source file and replaces all
@@ -122,139 +164,3 @@ flipBirdTracks f =
     flipBirdTrack :: Text -> Text
     flipBirdTrack xs | Text.isPrefixOf ">" xs = " " <> Text.drop 1 xs
     flipBirdTrack _ = " "
-
-data ScannedData = ScannedData
-    { moduleName :: Text
-    , importedModules :: [ModuleImport]
-    , usesTH :: Bool
-    }
-
-scanTokenStream :: FilePath -> [Located Token] -> Either String ScannedData
-scanTokenStream fp toks =
-  case parse parser fp toks of
-    Left e -> Left (show e)
-    Right a -> Right a
-  where
-    parser = do
-      langExts <- concat <$> many parseLanguagePragma
-      modName <- parseModuleHeader <|> return "Main"
-      optional $ satisfy "virtual brace" $ \case ITvocurly -> Just (); _ -> Nothing
-      skipMany comment
-      imports <- many parseImport
-      return ScannedData
-        { moduleName = modName
-        , importedModules = nub imports
-        , usesTH = any (`elem` ["TemplateHaskell", "QuasiQuotes"]) langExts
-        }
-
-    parseLanguagePragma :: Parsec [Located Token] () [String]
-    parseLanguagePragma = do
-      satisfyEvenComments "LANGUAGE pragma" $ \case
-        ITblockComment s -> Just (getLanguageExtensionsMaybe s)
-        ITlineComment _ -> Just []
-        _ -> Nothing
-
-    parseModuleHeader = do
-      satisfy "module" $ \case
-        ITmodule -> Just ()
-        _ -> Nothing
-      parseModuleName <* parseHeaderTail
-
-    parseHeaderTail = do
-      skipMany $ satisfy "not where" $ \case ITwhere -> Nothing; _ -> Just ()
-      satisfy "where" $ \case ITwhere -> Just (); _ -> Nothing
-
-    parseModuleName = flip labels ["ITqconid", "ITconid"] $ do
-      satisfy "a module name" $ \case
-        ITqconid (q, n) -> Just $ Text.pack $ unpackFS (q <> "." <> n)
-        ITconid n -> Just $ Text.pack $ unpackFS n
-        _ -> Nothing
-
-    parseImport = do
-      satisfy "import" $ \case ITimport -> Just (); _ -> Nothing
-      optional $ satisfy "qualified" $ \case ITqualified -> Just (); _ -> Nothing
-      maybePackageName <- optionMaybe parseString
-      moduleName <- parseModuleName <* parseImportTail
-      return $ ModuleImport maybePackageName moduleName
-
-    parseString = satisfy "string" $ \case
-      ITstring _ str -> Just $ Text.pack $ unpackFS str
-      _ -> Nothing
-
-    parseImportTail = do
-      optional $ satisfy "qualified" $ \case ITqualified -> Just (); _ -> Nothing
-      optional $ do
-        satisfy "as" $ \case ITas -> Just (); _ -> Nothing
-        parseModuleName
-      optional $ satisfy "hiding" $ \case IThiding -> Just (); _ -> Nothing
-      optional parseNestedParens
-      optional $ satisfy ";" $ \case ITsemi -> Just (); _ -> Nothing
-
-    parseNestedParens = flip label "nested parentheses" $ do
-      satisfy "(" $ \case IToparen -> Just (); _ -> Nothing
-      skipMany $ satisfy "not ( or )" $ \case IToparen -> Nothing; ITcparen -> Nothing; _ -> Just ()
-      skipMany $ do
-        parseNestedParens
-        skipMany $ satisfy "not ( or )" $ \case IToparen -> Nothing; ITcparen -> Nothing; _ -> Just ()
-      satisfy ")" $ \case ITcparen -> Just (); _ -> Nothing
-
-    satisfy lbl f = satisfyEvenComments lbl f <* skipMany comment
-
-    satisfyEvenComments lbl f =
-      token (show . unLoc) locToSourcePos (f . unLoc) <?> lbl
-
-    comment :: Parsec [Located Token] () String
-    comment =
-      satisfyEvenComments "comment" (\case
-        ITblockComment c -> Just c
-        ITlineComment c -> Just c
-        _ -> Nothing
-      ) <* optional (satisfyEvenComments ";" $ \case ITsemi -> Just (); _ -> Nothing)
-
-    locToSourcePos :: Located a -> SourcePos
-    locToSourcePos loc =
-      let srcSpan = getLoc loc
-       in case srcSpanStart srcSpan of
-            RealSrcLoc realSrcLoc ->
-              newPos fp (srcLocLine realSrcLoc) (srcLocCol realSrcLoc)
-            _ ->
-              newPos fp 0 0
-
-getLanguageExtensionsMaybe :: String -> [String]
-getLanguageExtensionsMaybe = \case
-    '{':'-':'#':s0 ->
-      case dropWhile isSpace s0 of
-        'L':'A':'N':'G':'U':'A':'G':'E':x:s1 | isSpace x ->
-          readLanguageExtensions [] s1
-        _ ->
-          []
-    _ ->
-      []
-  where
-    readLanguageExtensions acc s =
-      case takeLanguageExtension s of
-        (e, rest) | not (null e) -> readLanguageExtensions (e : acc) rest
-        _ -> acc
-
-    takeLanguageExtension s =
-      span isAlphaNum $
-      dropWhile (\x -> isSpace x || x == ',') s
-
-lexTokenStream :: StringBuffer -> RealSrcLoc -> [Located Token]
-lexTokenStream buf loc =
-  let allExtensions = [minBound..maxBound]
-      parserFlags = mkParserFlags'
-        GHC.empty
-        (GHC.fromList allExtensions)
-        (error "lexTokenStreamUnitId")
-        False
-        False
-        True
-        True
-      initState = mkPStatePure parserFlags buf loc
-   in go initState
-  where
-    go st = case unP (lexer False return) st of
-      POk _st' (unLoc -> ITeof) -> []
-      POk st' tok -> tok : go st'
-      PFailed st' -> error $ "Lexer error at " ++ show (GHC.loc st')
diff --git a/himportscan/tests/HImportScan/ImportScannerSpec.hs b/himportscan/tests/HImportScan/ImportScannerSpec.hs
index 1ebdaf2..5d42e39 100644
--- a/himportscan/tests/HImportScan/ImportScannerSpec.hs
+++ b/himportscan/tests/HImportScan/ImportScannerSpec.hs
@@ -1,14 +1,17 @@
 {-# LANGUAGE NamedFieldPuns #-}
+{-# LANGUAGE OverloadedLists #-}
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE QuasiQuotes #-}
 module HImportScan.ImportScannerSpec where
 
 import Data.Char (isSpace)
+import Data.Set (Set)
+import qualified Data.Set as Set
 import Data.String.QQ (s)
-import Test.Hspec
-import HImportScan.ImportScanner (ModuleImport(..), ScannedImports(..), scanImports)
 import Data.Text (Text)
 import qualified Data.Text as Text
+import HImportScan.ImportScanner (ModuleImport(..), ScannedImports(..), scanImports)
+import Test.Hspec
 
 
 -- | This type provides some pretty printing for reporting
@@ -25,7 +28,7 @@ showScannedImports si = Text.unlines $ map ("    " <>) $
     , filePath si
     , moduleName si
     ] ++
-    map (("  " <>) . showImport) (importedModules si) ++
+    map (("  " <>) . showImport) (Set.toList $ importedModules si) ++
     [ "usesTH = " <> Text.pack (show $ usesTH si)
     ]
   where
@@ -47,13 +50,13 @@ stripIndentation t =
       let (spaces, rest) = Text.span isSpace line
        in if Text.length rest == 0 then maxBound else Text.length spaces
 
-testSource :: Text -> [ModuleImport] -> Bool -> Text -> IO ()
+testSource :: Text -> Set ModuleImport -> Bool -> Text -> IO ()
 testSource = testSourceWithFile "dummy.hs"
 
-testSourceWithFile :: FilePath -> Text -> [ModuleImport] -> Bool -> Text -> IO ()
+testSourceWithFile :: FilePath -> Text -> Set ModuleImport -> Bool -> Text -> IO ()
 testSourceWithFile file moduleName importedModules usesTH contents = do
-    NicelyPrinted (scanImports file $ stripIndentation contents)
-      `shouldBe` NicelyPrinted ScannedImports
+    fmap NicelyPrinted (scanImports file $ stripIndentation contents)
+      `shouldReturn` NicelyPrinted ScannedImports
         { filePath = Text.pack file
         , moduleName
         , importedModules
diff --git a/tests/alternative-deps/WORKSPACE b/tests/alternative-deps/WORKSPACE
index 066b80e..e90651a 100644
--- a/tests/alternative-deps/WORKSPACE
+++ b/tests/alternative-deps/WORKSPACE
@@ -45,14 +45,12 @@ load("@io_tweag_gazelle_haskell_modules//:defs.bzl", "gazelle_haskell_modules_de
 
 gazelle_haskell_modules_dependencies(
     aeson = "@stackage-b//:aeson",
-    parsec = "@stackage-b//:parsec",
 )
 
 stack_snapshot(
     name = "stackage-b",
     packages = [
         "aeson",
-        "parsec",
     ],
     snapshot = "lts-18.1",
 )