Skip to content

Commit

Permalink
Make changes backwards-compatible
Browse files Browse the repository at this point in the history
  • Loading branch information
anka-213 committed Mar 29, 2021
1 parent ddd3c1e commit 06607c5
Show file tree
Hide file tree
Showing 6 changed files with 76 additions and 27 deletions.
49 changes: 49 additions & 0 deletions src/HieDb/Compat.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,49 @@

{-# LANGUAGE CPP #-}
module HieDb.Compat where

import Compat.HieTypes

#if __GLASGOW_HASKELL__ >= 900
import Compat.HieUtils

import qualified Data.Map as M
import qualified Data.Set as S


-- nodeInfo' :: Ord a => HieAST a -> NodeInfo a
nodeInfo' :: HieAST TypeIndex -> NodeInfo TypeIndex
nodeInfo' = M.foldl' combineNodeInfo' emptyNodeInfo . getSourcedNodeInfo . sourcedNodeInfo

combineNodeInfo' :: Ord a => NodeInfo a -> NodeInfo a -> NodeInfo a
(NodeInfo as ai ad) `combineNodeInfo'` (NodeInfo bs bi bd) =
NodeInfo (S.union as bs) (mergeSorted ai bi) (M.unionWith (<>) ad bd)
where
mergeSorted :: Ord a => [a] -> [a] -> [a]
mergeSorted la@(a:as) lb@(b:bs) = case compare a b of
LT -> a : mergeSorted as lb
EQ -> a : mergeSorted as bs
GT -> b : mergeSorted la bs
mergeSorted as [] = as
mergeSorted [] bs = bs
#else
import qualified FastString as FS

import Module

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__ >= 900
#else
#endif
3 changes: 2 additions & 1 deletion src/HieDb/Create.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,9 +32,10 @@ import System.Directory

import Database.SQLite.Simple

import HieDb.Compat
import HieDb.Types
import HieDb.Utils
import GHC.Data.FastString as FS ( FastString )
import FastString as FS ( FastString )

sCHEMA_VERSION :: Integer
sCHEMA_VERSION = 5
Expand Down
1 change: 1 addition & 0 deletions src/HieDb/Query.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,7 @@ import Data.IORef
import Database.SQLite.Simple

import HieDb.Dump (sourceCode)
import HieDb.Compat
import HieDb.Types
import HieDb.Utils
import qualified HieDb.Html as Html
Expand Down
6 changes: 6 additions & 0 deletions src/HieDb/Run.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE BlockArguments #-}
Expand Down Expand Up @@ -49,6 +50,7 @@ import qualified Data.ByteString.Char8 as BS
import Options.Applicative

import HieDb
import HieDb.Compat
import HieDb.Dump

hiedbMain :: LibDir -> IO ()
Expand Down Expand Up @@ -362,7 +364,11 @@ 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
11 changes: 4 additions & 7 deletions src/HieDb/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,8 @@ import Database.SQLite.Simple.FromField

import qualified Text.ParserCombinators.ReadP as R

import HieDb.Compat

newtype HieDb = HieDb { getConn :: Connection }

data HieDbException
Expand Down Expand Up @@ -80,16 +82,11 @@ instance ToField ModuleName where
instance FromField ModuleName where
fromField fld = mkModuleName . T.unpack <$> fromField fld

instance ToField (GenUnit UnitId) where
instance ToField Unit where
toField uid = SQLText $ T.pack $ unitString uid
instance FromField (GenUnit UnitId) where
instance FromField Unit where
fromField fld = stringToUnit . T.unpack <$> fromField fld

instance ToField UnitId where
toField uid = SQLText $ T.pack $ unitIdString uid
instance FromField UnitId where
fromField fld = stringToUnitId . T.unpack <$> fromField fld

instance ToField Fingerprint where
toField hash = SQLText $ T.pack $ show hash
instance FromField Fingerprint where
Expand Down
33 changes: 14 additions & 19 deletions src/HieDb/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,6 @@ import DynFlags
import SysTools

import qualified Data.Map as M
import qualified Data.Set as S

import qualified FastString as FS

Expand All @@ -46,6 +45,7 @@ import Data.Monoid
import Data.IORef

import HieDb.Types
import HieDb.Compat
import Database.SQLite.Simple

addTypeRef :: HieDb -> FilePath -> A.Array TypeIndex HieTypeFlat -> A.Array TypeIndex (Maybe Int64) -> RealSrcSpan -> TypeIndex -> IO ()
Expand All @@ -72,8 +72,11 @@ addTypeRef (getConn -> conn) hf arr ixs sp = go 0
#endif
HTyConApp _ (HieArgs xs) -> mapM_ (next . snd) xs
HForAllTy ((_ , a),_) b -> mapM_ next [a,b]
-- HFunTy a b -> mapM_ next [a,b]
HFunTy 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 d a
Expand Down Expand Up @@ -117,7 +120,11 @@ findDefInFile occ mdl file = do
nc <- readIORef ncr
return $ case lookupOrigNameCache (nsNames nc) 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 (FS.unpackFS $ unhelpfulSpanFS msg)
Nothing -> Left $ NameNotFound occ (Just $ moduleName mdl) (Just $ moduleUnit mdl)

Expand Down Expand Up @@ -200,7 +207,11 @@ 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 Expand Up @@ -229,19 +240,3 @@ identifierTree [email protected]{ nodeChildren } =
{ rootLabel = nd { nodeChildren = mempty }
, subForest = map identifierTree nodeChildren
}

-- nodeInfo' :: Ord a => HieAST a -> NodeInfo a
nodeInfo' :: HieAST TypeIndex -> NodeInfo TypeIndex
nodeInfo' = M.foldl' combineNodeInfo' emptyNodeInfo . getSourcedNodeInfo . sourcedNodeInfo

combineNodeInfo' :: Ord a => NodeInfo a -> NodeInfo a -> NodeInfo a
(NodeInfo as ai ad) `combineNodeInfo'` (NodeInfo bs bi bd) =
NodeInfo (S.union as bs) (mergeSorted ai bi) (M.unionWith (<>) ad bd)
where
mergeSorted :: Ord a => [a] -> [a] -> [a]
mergeSorted la@(a:as) lb@(b:bs) = case compare a b of
LT -> a : mergeSorted as lb
EQ -> a : mergeSorted as bs
GT -> b : mergeSorted la bs
mergeSorted as [] = as
mergeSorted [] bs = bs

0 comments on commit 06607c5

Please sign in to comment.