#include "HsVersions.h"
module GHC.Types.Avail (
Avails,
AvailInfo(..),
avail,
availField,
availTC,
availsToNameSet,
availsToNameSetWithSelectors,
availsToNameEnv,
availExportsDecl,
availName, availGreName,
availNames, availNonFldNames,
availNamesWithSelectors,
availFlds,
availGreNames,
availSubordinateGreNames,
stableAvailCmp,
plusAvail,
trimAvail,
filterAvail,
filterAvails,
nubAvails,
GreName(..),
greNameMangledName,
greNamePrintableName,
greNameSrcSpan,
greNameFieldLabel,
partitionGreNames,
stableGreNameCmp,
) where
import GHC.Prelude
import GHC.Types.Name
import GHC.Types.Name.Env
import GHC.Types.Name.Set
import GHC.Types.SrcLoc
import GHC.Types.FieldLabel
import GHC.Utils.Binary
import GHC.Data.List.SetOps
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Utils.Misc
import Data.Data ( Data )
import Data.Either ( partitionEithers )
import Data.List ( find )
import Data.Maybe
data AvailInfo
= Avail GreName
| AvailTC
Name
[GreName]
deriving ( Eq
, Data )
type Avails = [AvailInfo]
stableAvailCmp :: AvailInfo -> AvailInfo -> Ordering
stableAvailCmp (Avail c1) (Avail c2) = c1 `stableGreNameCmp` c2
stableAvailCmp (Avail {}) (AvailTC {}) = LT
stableAvailCmp (AvailTC n ns) (AvailTC m ms) = (n `stableNameCmp` m) `thenCmp`
(cmpList stableGreNameCmp ns ms)
stableAvailCmp (AvailTC {}) (Avail {}) = GT
stableGreNameCmp :: GreName -> GreName -> Ordering
stableGreNameCmp (NormalGreName n1) (NormalGreName n2) = n1 `stableNameCmp` n2
stableGreNameCmp (NormalGreName {}) (FieldGreName {}) = LT
stableGreNameCmp (FieldGreName f1) (FieldGreName f2) = flSelector f1 `stableNameCmp` flSelector f2
stableGreNameCmp (FieldGreName {}) (NormalGreName {}) = GT
avail :: Name -> AvailInfo
avail n = Avail (NormalGreName n)
availField :: FieldLabel -> AvailInfo
availField fl = Avail (FieldGreName fl)
availTC :: Name -> [Name] -> [FieldLabel] -> AvailInfo
availTC n ns fls = AvailTC n (map NormalGreName ns ++ map FieldGreName fls)
availsToNameSet :: [AvailInfo] -> NameSet
availsToNameSet avails = foldr add emptyNameSet avails
where add avail set = extendNameSetList set (availNames avail)
availsToNameSetWithSelectors :: [AvailInfo] -> NameSet
availsToNameSetWithSelectors avails = foldr add emptyNameSet avails
where add avail set = extendNameSetList set (availNamesWithSelectors avail)
availsToNameEnv :: [AvailInfo] -> NameEnv AvailInfo
availsToNameEnv avails = foldr add emptyNameEnv avails
where add avail env = extendNameEnvList env
(zip (availNames avail) (repeat avail))
availExportsDecl :: AvailInfo -> Bool
availExportsDecl (AvailTC ty_name names)
| n : _ <- names = NormalGreName ty_name == n
| otherwise = False
availExportsDecl _ = True
availName :: AvailInfo -> Name
availName (Avail n) = greNameMangledName n
availName (AvailTC n _) = n
availGreName :: AvailInfo -> GreName
availGreName (Avail c) = c
availGreName (AvailTC n _) = NormalGreName n
availNames :: AvailInfo -> [Name]
availNames (Avail c) = childNonOverloadedNames c
availNames (AvailTC _ cs) = concatMap childNonOverloadedNames cs
childNonOverloadedNames :: GreName -> [Name]
childNonOverloadedNames (NormalGreName n) = [n]
childNonOverloadedNames (FieldGreName fl) = [ flSelector fl | not (flIsOverloaded fl) ]
availNamesWithSelectors :: AvailInfo -> [Name]
availNamesWithSelectors (Avail c) = [greNameMangledName c]
availNamesWithSelectors (AvailTC _ cs) = map greNameMangledName cs
availNonFldNames :: AvailInfo -> [Name]
availNonFldNames (Avail (NormalGreName n)) = [n]
availNonFldNames (Avail (FieldGreName {})) = []
availNonFldNames (AvailTC _ ns) = mapMaybe f ns
where
f (NormalGreName n) = Just n
f (FieldGreName {}) = Nothing
availFlds :: AvailInfo -> [FieldLabel]
availFlds (Avail c) = maybeToList (greNameFieldLabel c)
availFlds (AvailTC _ cs) = mapMaybe greNameFieldLabel cs
availGreNames :: AvailInfo -> [GreName]
availGreNames (Avail c) = [c]
availGreNames (AvailTC _ cs) = cs
availSubordinateGreNames :: AvailInfo -> [GreName]
availSubordinateGreNames (Avail {}) = []
availSubordinateGreNames avail@(AvailTC _ ns)
| availExportsDecl avail = tail ns
| otherwise = ns
data GreName = NormalGreName Name
| FieldGreName FieldLabel
deriving (Data, Eq)
instance Outputable GreName where
ppr (NormalGreName n) = ppr n
ppr (FieldGreName fl) = ppr fl
instance HasOccName GreName where
occName (NormalGreName n) = occName n
occName (FieldGreName fl) = occName fl
greNameMangledName :: GreName -> Name
greNameMangledName (NormalGreName n) = n
greNameMangledName (FieldGreName fl) = flSelector fl
greNamePrintableName :: GreName -> Name
greNamePrintableName (NormalGreName n) = n
greNamePrintableName (FieldGreName fl) = fieldLabelPrintableName fl
greNameSrcSpan :: GreName -> SrcSpan
greNameSrcSpan (NormalGreName n) = nameSrcSpan n
greNameSrcSpan (FieldGreName fl) = nameSrcSpan (flSelector fl)
greNameFieldLabel :: GreName -> Maybe FieldLabel
greNameFieldLabel (NormalGreName {}) = Nothing
greNameFieldLabel (FieldGreName fl) = Just fl
partitionGreNames :: [GreName] -> ([Name], [FieldLabel])
partitionGreNames = partitionEithers . map to_either
where
to_either (NormalGreName n) = Left n
to_either (FieldGreName fl) = Right fl
plusAvail :: AvailInfo -> AvailInfo -> AvailInfo
plusAvail a1 a2
| debugIsOn && availName a1 /= availName a2
= pprPanic "GHC.Rename.Env.plusAvail names differ" (hsep [ppr a1,ppr a2])
plusAvail a1@(Avail {}) (Avail {}) = a1
plusAvail (AvailTC _ []) a2@(AvailTC {}) = a2
plusAvail a1@(AvailTC {}) (AvailTC _ []) = a1
plusAvail (AvailTC n1 (s1:ss1)) (AvailTC n2 (s2:ss2))
= case (NormalGreName n1==s1, NormalGreName n2==s2) of
(True,True) -> AvailTC n1 (s1 : (ss1 `unionLists` ss2))
(True,False) -> AvailTC n1 (s1 : (ss1 `unionLists` (s2:ss2)))
(False,True) -> AvailTC n1 (s2 : ((s1:ss1) `unionLists` ss2))
(False,False) -> AvailTC n1 ((s1:ss1) `unionLists` (s2:ss2))
plusAvail a1 a2 = pprPanic "GHC.Rename.Env.plusAvail" (hsep [ppr a1,ppr a2])
trimAvail :: AvailInfo -> Name -> AvailInfo
trimAvail avail@(Avail {}) _ = avail
trimAvail avail@(AvailTC n ns) m = case find ((== m) . greNameMangledName) ns of
Just c -> AvailTC n [c]
Nothing -> pprPanic "trimAvail" (hsep [ppr avail, ppr m])
filterAvails :: (Name -> Bool) -> [AvailInfo] -> [AvailInfo]
filterAvails keep avails = foldr (filterAvail keep) [] avails
filterAvail :: (Name -> Bool) -> AvailInfo -> [AvailInfo] -> [AvailInfo]
filterAvail keep ie rest =
case ie of
Avail c | keep (greNameMangledName c) -> ie : rest
| otherwise -> rest
AvailTC tc cs ->
let cs' = filter (keep . greNameMangledName) cs
in if null cs' then rest else AvailTC tc cs' : rest
nubAvails :: [AvailInfo] -> [AvailInfo]
nubAvails avails = nameEnvElts (foldl' add emptyNameEnv avails)
where
add env avail = extendNameEnv_C plusAvail env (availName avail) avail
instance Outputable AvailInfo where
ppr = pprAvail
pprAvail :: AvailInfo -> SDoc
pprAvail (Avail n)
= ppr n
pprAvail (AvailTC n ns)
= ppr n <> braces (fsep (punctuate comma (map ppr ns)))
instance Binary AvailInfo where
put_ bh (Avail aa) = do
putByte bh 0
put_ bh aa
put_ bh (AvailTC ab ac) = do
putByte bh 1
put_ bh ab
put_ bh ac
get bh = do
h <- getByte bh
case h of
0 -> do aa <- get bh
return (Avail aa)
_ -> do ab <- get bh
ac <- get bh
return (AvailTC ab ac)
instance Binary GreName where
put_ bh (NormalGreName aa) = do
putByte bh 0
put_ bh aa
put_ bh (FieldGreName ab) = do
putByte bh 1
put_ bh ab
get bh = do
h <- getByte bh
case h of
0 -> do aa <- get bh
return (NormalGreName aa)
_ -> do ab <- get bh
return (FieldGreName ab)