Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- newtype StableName = MkStableName {
- unStableName :: Name
- mkStableName :: Name -> StableName
- availsToStableNameSet :: [AvailInfo] -> HashSet StableName
- data MGIModGuts = MI {
- mgi_binds :: !CoreProgram
- mgi_module :: !Module
- mgi_deps :: !Dependencies
- mgi_dir_imps :: ![ModuleName]
- mgi_rdr_env :: !GlobalRdrEnv
- mgi_tcs :: ![TyCon]
- mgi_fam_insts :: ![FamInst]
- mgi_exports :: !(HashSet StableName)
- mgi_cls_inst :: !(Maybe [ClsInst])
- miModGuts :: Maybe [ClsInst] -> ModGuts -> MGIModGuts
- nameSetToStableNameSet :: NameSet -> HashSet StableName
- mg_dir_imps :: ModGuts -> [ModuleName]
- mgi_namestring :: MGIModGuts -> String
Documentation
newtype StableName #
A StableName
is virtually isomorphic to a GHC's Name
but crucially we don't use
the Eq
instance defined on a Name
because it's Unique
-based. In particular, GHC
doesn't guarantee that if we load an interface multiple times we would get the same Unique
for the
same Name
, and this is a problem when we rely on Name
s to be the same when we call isExportedVar
,
which used to use a NameSet
derived from the '[AvailInfo]'. As the name implies, a NameSet
uses a
Name
s Unique
for duplicate detection and indexing, and this would lead to Var
s being resolved to
a Name
which is basically the same, but it has a different Unique
, and that would cause the lookup
inside the NameSet
to fail.
Instances
Eq StableName # | |
Defined in Language.Haskell.Liquid.GHC.Types (==) :: StableName -> StableName -> Bool # (/=) :: StableName -> StableName -> Bool # | |
Show StableName # | |
Defined in Language.Haskell.Liquid.GHC.Types showsPrec :: Int -> StableName -> ShowS # show :: StableName -> String # showList :: [StableName] -> ShowS # | |
Generic StableName # | |
Defined in Language.Haskell.Liquid.GHC.Types type Rep StableName :: Type -> Type # from :: StableName -> Rep StableName x # to :: Rep StableName x -> StableName # | |
Hashable StableName # | |
Defined in Language.Haskell.Liquid.GHC.Types hashWithSalt :: Int -> StableName -> Int hash :: StableName -> Int | |
type Rep StableName # | |
Defined in Language.Haskell.Liquid.GHC.Types type Rep StableName = D1 ('MetaData "StableName" "Language.Haskell.Liquid.GHC.Types" "liquidhaskell-0.8.10.1-inplace" 'True) (C1 ('MetaCons "MkStableName" 'PrefixI 'True) (S1 ('MetaSel ('Just "unStableName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))) |
mkStableName :: Name -> StableName #
Creates a new StableName
out of a Name
.
availsToStableNameSet :: [AvailInfo] -> HashSet StableName #
Converts a list of AvailInfo
into a "StableNameSet", similarly to what availsToNameSet
would do.
data MGIModGuts #
Datatype For Holding GHC ModGuts ------------------------------------------
MI | |
|
nameSetToStableNameSet :: NameSet -> HashSet StableName #
mg_dir_imps :: ModGuts -> [ModuleName] #
mgi_namestring :: MGIModGuts -> String #