{-# LANGUAGE CPP, PatternSynonyms, ViewPatterns #-}
module HieDb.Compat (
nodeInfo'
, Unit
, unitString
, stringToUnit
, moduleUnit
, unhelpfulSpanFS
, ModuleName
, mkModuleName
, moduleName
, moduleNameString
, Fingerprint
, unpackFS
, readHexFingerprint
, getFileHash
, NameSpace
, OccName
, mkOccName
, nameOccName
, occNameSpace
, occNameString
, mkVarOccFS
, Name
, nameSrcSpan
, NameCacheUpdater(..)
, NameCache
, nsNames
, initNameCache
, lookupOrigNameCache
, Module
, mkModule
, nameModule_maybe
, nameModule
, varName
, isVarNameSpace
, dataName
, isDataConNameSpace
, tcClsName
, isTcClsNameSpace
, tvName
, isTvNameSpace
, flLabel
, DynFlags
, defaultDynFlags
, LlvmConfig(..)
, Avail.AvailInfo
, pattern AvailName
, pattern AvailFL
, pattern AvailTC
, flSelector
, SrcSpan(..)
, RealSrcSpan
, mkRealSrcLoc
, mkRealSrcSpan
, srcSpanStartLine
, srcSpanStartCol
, srcSpanEndLine
, srcSpanEndCol
, mkSplitUniqSupply
, initSysTools
, HiePath
, hiePathToFS
, (<+>)
, ppr
, showSDoc
, hang
, text
, FastString
, IfaceType
, IfaceTyCon(..)
) where
import Compat.HieTypes
#if __GLASGOW_HASKELL__ >= 900
import GHC.Data.FastString as FS
import GHC.Driver.Session
import GHC.Iface.Env
import GHC.Iface.Type
import GHC.SysTools
import qualified GHC.Types.Avail as Avail
import GHC.Types.FieldLabel
import GHC.Types.Name
import GHC.Types.Name.Cache
import GHC.Types.Unique.Supply
import GHC.Unit.Types
import GHC.Unit.Module.Name
import GHC.Utils.Fingerprint
#if __GLASGOW_HASKELL__ >= 902
import GHC.Driver.Ppr (showSDoc)
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
#if __GLASGOW_HASKELL__ >= 900
import GHC.Types.SrcLoc
import Compat.HieUtils
import qualified Data.Map as M
import qualified Data.Set as S
nodeInfo' :: HieAST TypeIndex -> NodeInfo TypeIndex
nodeInfo' :: HieAST TypeIndex -> NodeInfo TypeIndex
nodeInfo' = forall a b k. (a -> b -> a) -> a -> Map k b -> a
M.foldl' forall a. Ord a => NodeInfo a -> NodeInfo a -> NodeInfo a
combineNodeInfo' forall a. NodeInfo a
emptyNodeInfo forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. SourcedNodeInfo a -> Map NodeOrigin (NodeInfo a)
getSourcedNodeInfo forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. HieAST a -> SourcedNodeInfo a
sourcedNodeInfo
combineNodeInfo' :: Ord a => NodeInfo a -> NodeInfo a -> NodeInfo a
(NodeInfo Set NodeAnnotation
as [a]
ai NodeIdentifiers a
ad) combineNodeInfo' :: forall a. Ord a => NodeInfo a -> NodeInfo a -> NodeInfo a
`combineNodeInfo'` (NodeInfo Set NodeAnnotation
bs [a]
bi NodeIdentifiers a
bd) =
forall a.
Set NodeAnnotation -> [a] -> NodeIdentifiers a -> NodeInfo a
NodeInfo (forall a. Ord a => Set a -> Set a -> Set a
S.union Set NodeAnnotation
as Set NodeAnnotation
bs) (forall a. Ord a => [a] -> [a] -> [a]
mergeSorted [a]
ai [a]
bi) (forall k a. Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
M.unionWith forall a. Semigroup a => a -> a -> a
(<>) NodeIdentifiers a
ad NodeIdentifiers a
bd)
where
mergeSorted :: Ord a => [a] -> [a] -> [a]
mergeSorted :: forall a. Ord a => [a] -> [a] -> [a]
mergeSorted la :: [a]
la@(a
a:[a]
as) lb :: [a]
lb@(a
b:[a]
bs) = case forall a. Ord a => a -> a -> Ordering
compare a
a a
b of
Ordering
LT -> a
a forall a. a -> [a] -> [a]
: forall a. Ord a => [a] -> [a] -> [a]
mergeSorted [a]
as [a]
lb
Ordering
EQ -> a
a forall a. a -> [a] -> [a]
: forall a. Ord a => [a] -> [a] -> [a]
mergeSorted [a]
as [a]
bs
Ordering
GT -> a
b forall a. a -> [a] -> [a]
: forall a. Ord a => [a] -> [a] -> [a]
mergeSorted [a]
la [a]
bs
mergeSorted [a]
as [] = [a]
as
mergeSorted [] [a]
bs = [a]
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
#endif
hiePathToFS :: HiePath -> FastString
#if __GLASGOW_HASKELL__ >= 902
hiePathToFS :: HiePath -> FastString
hiePathToFS (LexicalFastString FastString
fs) = FastString
fs
#else
hiePathToFS fs = fs
#endif
{-# COMPLETE AvailTC, AvailName, AvailFL #-}
pattern AvailTC :: Name -> [Name] -> [FieldLabel] -> Avail.AvailInfo
#if __GLASGOW_HASKELL__ >= 902
pattern $mAvailTC :: forall {r}.
AvailInfo
-> (Name -> [Name] -> [FieldLabel] -> r) -> ((# #) -> r) -> r
AvailTC n names pieces <- Avail.AvailTC n ((\[GreName]
gres -> forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\GreName
gre ([Name]
names, [FieldLabel]
pieces) -> case GreName
gre of
Avail.NormalGreName Name
name -> (Name
nameforall a. a -> [a] -> [a]
: [Name]
names, [FieldLabel]
pieces)
Avail.FieldGreName FieldLabel
label -> ([Name]
names, FieldLabel
labelforall a. a -> [a] -> [a]
:[FieldLabel]
pieces)) ([], []) [GreName]
gres) -> (names, pieces))
#else
pattern AvailTC n names pieces <- Avail.AvailTC n names pieces
#endif
pattern AvailName :: Name -> Avail.AvailInfo
#if __GLASGOW_HASKELL__ >= 902
pattern $mAvailName :: forall {r}. AvailInfo -> (Name -> r) -> ((# #) -> r) -> r
AvailName n <- Avail.Avail (Avail.NormalGreName n)
#else
pattern AvailName n <- Avail.Avail n
#endif
pattern AvailFL :: FieldLabel -> Avail.AvailInfo
#if __GLASGOW_HASKELL__ >= 902
pattern $mAvailFL :: forall {r}. AvailInfo -> (FieldLabel -> r) -> ((# #) -> r) -> r
AvailFL fl <- Avail.Avail (Avail.FieldGreName fl)
#else
pattern AvailFL x <- Avail.Avail ((\_ -> (True, undefined)) -> (False, x))
#endif
#if __GLASGOW_HASKELL__ >= 903
type NameCacheUpdater = NameCache
#endif