Skip to content

Commit

Permalink
Remove CPP for no longer supported GHC <9.0 (#70)
Browse files Browse the repository at this point in the history
* Remove CPP for no longer supported GHC <9.0

* More cleanups
  • Loading branch information
jhrcek authored Feb 15, 2024
1 parent e179a35 commit cf132f1
Show file tree
Hide file tree
Showing 6 changed files with 11 additions and 82 deletions.
6 changes: 4 additions & 2 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
# Revision history for hiedb

## 0.6.0.0 -- 2024-12-11
## 0.6.0.0 -- 2024-02-11

* Add index on column `unit` of table `mods`
* Add new table `imports` which indexes import statements
Expand All @@ -24,8 +24,10 @@
* Handle duplicate record fields in GHC 9.8 instead of crashing

## 0.4.4.0 -- 2023-11-13

* Add `--src-base-dir` option allowing for src file indexing in `mods`
* 9.8.1 support
* Support GHC 9.8.1
* Drop support for GHC 8.10
* Add `lookupHieFileFromHash`
* Add `lookupPackage`
* Add `removeDependencySrcFiles`
Expand Down
2 changes: 1 addition & 1 deletion hiedb.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -36,6 +36,7 @@ common common-options
-Wincomplete-uni-patterns
-Wpartial-fields
-Wredundant-constraints
-Wunused-packages
-Wno-name-shadowing

executable hiedb
Expand Down Expand Up @@ -84,7 +85,6 @@ test-suite hiedb-tests
build-tool-depends: hiedb:hiedb
build-depends: directory
, filepath
, ghc >= 8.6
, ghc-paths
, hiedb
, hspec
Expand Down
35 changes: 0 additions & 35 deletions src/HieDb/Compat.hs
Original file line number Diff line number Diff line change
Expand Up @@ -92,7 +92,6 @@ module HieDb.Compat (

import Compat.HieTypes

#if __GLASGOW_HASKELL__ >= 900
import GHC.Data.FastString as FS
import GHC.Driver.Session
import GHC.Iface.Env
Expand All @@ -118,29 +117,10 @@ import GHC.Utils.Outputable (ppr, (<+>), hang, text)
#else
import GHC.Utils.Outputable (showSDoc, ppr, (<+>), hang, text)
#endif
#else
import DynFlags
import FastString
import Fingerprint
import FieldLabel
import Module
import Name
import NameCache
import Outputable (showSDoc, ppr, (<+>), hang, text)
#if __GLASGOW_HASKELL__ < 903
import IfaceEnv (NameCacheUpdater(..))
#endif
import IfaceType
import UniqSupply
import SrcLoc
import SysTools
import qualified Avail
#endif

import qualified Algebra.Graph.AdjacencyMap as Graph
import qualified Algebra.Graph.AdjacencyMap.Algorithm as Graph

#if __GLASGOW_HASKELL__ >= 900
import GHC.Types.SrcLoc
import Compat.HieUtils

Expand All @@ -163,21 +143,6 @@ combineNodeInfo' :: Ord a => NodeInfo a -> NodeInfo a -> NodeInfo a
GT -> b : mergeSorted la bs
mergeSorted as [] = as
mergeSorted [] bs = bs
#else
import qualified FastString as FS

nodeInfo' :: HieAST TypeIndex -> NodeInfo TypeIndex
nodeInfo' = nodeInfo
type Unit = UnitId
unitString :: Unit -> String
unitString = unitIdString
stringToUnit :: String -> Unit
stringToUnit = stringToUnitId
moduleUnit :: Module -> Unit
moduleUnit = moduleUnitId
unhelpfulSpanFS :: FS.FastString -> FS.FastString
unhelpfulSpanFS = id
#endif

#if __GLASGOW_HASKELL__ < 902
type HiePath = FastString
Expand Down
4 changes: 0 additions & 4 deletions src/HieDb/Run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -392,11 +392,7 @@ runCommand libdir opts cmd = withHieDbAndFlags libdir (database opts) $ \dynFlag
reportAmbiguousErr opts (Left $ NoNameAtPoint target sp)
forM_ names $ \name -> do
case nameSrcSpan name of
#if __GLASGOW_HASKELL__ >= 900
RealSrcSpan dsp _ -> do
#else
RealSrcSpan dsp -> do
#endif
unless (quiet opts) $
hPutStrLn stderr $ unwords ["Name", ppName opts (nameOccName name),"at",ppSpan opts sp,"is defined at:"]
contents <- case nameModule_maybe name of
Expand Down
38 changes: 6 additions & 32 deletions src/HieDb/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,11 +17,9 @@ import Compat.HieBin
import Compat.HieTypes
import qualified Compat.HieTypes as HieTypes
import Compat.HieUtils
import Control.Monad (guard)
import qualified Data.Map as M
import qualified Data.Set as S


import System.Directory
import System.FilePath

Expand All @@ -43,7 +41,7 @@ import qualified Data.IntSet as ISet
import qualified Data.IntMap.Strict as IMap
import Data.IntMap.Strict (IntMap)
import Data.IntSet (IntSet)
import Control.Monad (unless)
import Control.Monad (guard, unless)

#if __GLASGOW_HASKELL__ >= 903
import Control.Concurrent.MVar (readMVar)
Expand Down Expand Up @@ -84,18 +82,10 @@ addTypeRef (getConn -> conn) hf arr ixs sp = go 0
let next = go (depth + 1)
case arr A.! i of
HTyVarTy _ -> pure ()
#if __GLASGOW_HASKELL__ >= 808
HAppTy x (HieArgs xs) -> mapM_ next (x:map snd xs)
#else
HAppTy x y -> mapM_ next [x,y]
#endif
HTyConApp _ (HieArgs xs) -> mapM_ (next . snd) xs
HForAllTy ((_ , a),_) b -> mapM_ next [a,b]
#if __GLASGOW_HASKELL__ >= 900
HFunTy a b c -> mapM_ next [a,b,c]
#else
HFunTy a b -> mapM_ next [a,b]
#endif
HQualTy a b -> mapM_ next [a,b]
HLitTy _ -> pure ()
HCastTy a -> go depth a
Expand Down Expand Up @@ -148,11 +138,7 @@ findDefInFile occ mdl file = do
#endif
return $ case lookupOrigNameCache nsns mdl occ of
Just name -> case nameSrcSpan name of
#if __GLASGOW_HASKELL__ >= 900
RealSrcSpan sp _ -> Right (sp, mdl)
#else
RealSrcSpan sp -> Right (sp, mdl)
#endif
UnhelpfulSpan msg -> Left $ NameUnhelpfulSpan name (unpackFS $ unhelpfulSpanFS msg)
Nothing -> Left $ NameNotFound occ (Just $ moduleName mdl) (Just $ moduleUnit mdl)

Expand All @@ -169,18 +155,10 @@ pointCommand hf (sl,sc) mep k =

dynFlagsForPrinting :: LibDir -> IO DynFlags
dynFlagsForPrinting (LibDir libdir) = do
systemSettings <- initSysTools
#if __GLASGOW_HASKELL__ >= 808
libdir
#else
(Just libdir)
#endif
#if __GLASGOW_HASKELL__ >= 905
systemSettings <- initSysTools libdir
return $ defaultDynFlags systemSettings
#elif __GLASGOW_HASKELL__ >= 810
return $ defaultDynFlags systemSettings $ LlvmConfig [] []
#else
return $ defaultDynFlags systemSettings ([], [])
#if __GLASGOW_HASKELL__ < 905
(LlvmConfig [] [])
#endif

isCons :: String -> Bool
Expand All @@ -195,10 +173,10 @@ data AstInfo =
, astInfoImports :: [ImportRow]
}

instance Semigroup AstInfo where
instance Semigroup AstInfo where
AstInfo r1 d1 i1 <> AstInfo r2 d2 i2 = AstInfo (r1 <> r2) (d1 <> d2) (i1 <> i2)

instance Monoid AstInfo where
instance Monoid AstInfo where
mempty = AstInfo [] [] []

genAstInfo :: FilePath -> Module -> M.Map Identifier [(Span, IdentifierDetails a)] -> AstInfo
Expand Down Expand Up @@ -262,11 +240,7 @@ genDefRow path smod refmap = genRows $ M.toList refmap
where
genRows = mapMaybe go
getSpan name dets
#if __GLASGOW_HASKELL__ >= 900
| RealSrcSpan sp _ <- nameSrcSpan name = Just sp
#else
| RealSrcSpan sp <- nameSrcSpan name = Just sp
#endif
| otherwise = do
(sp, _dets) <- find defSpan dets
pure sp
Expand Down
8 changes: 0 additions & 8 deletions test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -202,11 +202,7 @@ cliSpec =
, "Identifiers:"
, "Symbol:c:Data1Constructor1:Sub.Module2:main"
, "Data1Constructor1 defined at test/data/Sub/Module2.hs:11:7-23"
#if __GLASGOW_HASKELL__ >= 900
, " Details: Nothing {declaration of constructor bound at: test/data/Sub/Module2.hs:11:7-23}"
#else
, " IdentifierDetails Nothing {Decl ConDec (Just SrcSpanOneLine \"test/data/Sub/Module2.hs\" 11 7 24)}"
#endif
, "Types:\n"
]
it "correctly prints type signatures" $
Expand All @@ -217,11 +213,7 @@ cliSpec =
, "Identifiers:"
, "Symbol:v:not:GHC.Classes:ghc-prim"
, "not defined at <no location info>"
#if __GLASGOW_HASKELL__ >= 900
, " Details: Just Bool -> Bool {usage}"
#else
, " IdentifierDetails Just Bool -> Bool {Use}"
#endif
, "Types:"
, "Bool -> Bool"
, ""
Expand Down

0 comments on commit cf132f1

Please sign in to comment.