Skip to content
GitLab
Projects
Groups
Snippets
Help
Loading...
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
GHC
Project overview
Project overview
Details
Activity
Releases
Repository
Repository
Files
Commits
Branches
Tags
Contributors
Graph
Compare
Locked Files
Issues
0
Issues
0
List
Boards
Labels
Service Desk
Milestones
Iterations
Merge Requests
0
Merge Requests
0
Requirements
Requirements
List
CI / CD
CI / CD
Pipelines
Jobs
Schedules
Security & Compliance
Security & Compliance
Dependency List
License Compliance
Operations
Operations
Incidents
Environments
Packages & Registries
Packages & Registries
Package Registry
Container Registry
Analytics
Analytics
CI / CD
Code Review
Insights
Issue
Repository
Value Stream
Wiki
Wiki
Snippets
Snippets
Members
Members
Collapse sidebar
Close sidebar
Activity
Graph
Create a new issue
Jobs
Commits
Issue Boards
Open sidebar
jberryman
GHC
Commits
94e7c6bf
Commit
94e7c6bf
authored
Sep 17, 2011
by
Simon Marlow
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
move AvailInfo and related things into its own module
parent
222589a9
Changes
19
Hide whitespace changes
Inline
Side-by-side
Showing
19 changed files
with
149 additions
and
108 deletions
+149
-108
compiler/basicTypes/Avail.hs
compiler/basicTypes/Avail.hs
+107
-0
compiler/deSugar/Desugar.lhs
compiler/deSugar/Desugar.lhs
+1
-0
compiler/ghc.cabal.in
compiler/ghc.cabal.in
+1
-0
compiler/iface/BinIface.hs
compiler/iface/BinIface.hs
+1
-0
compiler/iface/IfaceEnv.lhs
compiler/iface/IfaceEnv.lhs
+1
-0
compiler/iface/LoadIface.lhs
compiler/iface/LoadIface.lhs
+1
-0
compiler/iface/MkIface.lhs
compiler/iface/MkIface.lhs
+1
-0
compiler/main/GHC.hs
compiler/main/GHC.hs
+2
-2
compiler/main/HscTypes.lhs
compiler/main/HscTypes.lhs
+5
-79
compiler/main/InteractiveEval.hs
compiler/main/InteractiveEval.hs
+1
-0
compiler/main/TidyPgm.lhs
compiler/main/TidyPgm.lhs
+2
-1
compiler/prelude/PrelInfo.lhs
compiler/prelude/PrelInfo.lhs
+13
-14
compiler/rename/RnBinds.lhs
compiler/rename/RnBinds.lhs
+2
-5
compiler/rename/RnEnv.lhs
compiler/rename/RnEnv.lhs
+3
-2
compiler/rename/RnNames.lhs
compiler/rename/RnNames.lhs
+1
-0
compiler/rename/RnSource.lhs
compiler/rename/RnSource.lhs
+4
-5
compiler/typecheck/TcRnDriver.lhs
compiler/typecheck/TcRnDriver.lhs
+1
-0
compiler/typecheck/TcRnTypes.lhs
compiler/typecheck/TcRnTypes.lhs
+1
-0
compiler/typecheck/TcTyDecls.lhs
compiler/typecheck/TcTyDecls.lhs
+1
-0
No files found.
compiler/basicTypes/Avail.hs
0 → 100644
View file @
94e7c6bf
--
-- (c) The University of Glasgow
--
module
Avail
(
Avails
,
AvailInfo
(
..
),
availsToNameSet
,
availsToNameEnv
,
availName
,
availNames
,
stableAvailCmp
,
gresFromAvails
,
gresFromAvail
)
where
import
Name
import
NameEnv
import
NameSet
import
RdrName
import
Outputable
import
Util
-- -----------------------------------------------------------------------------
-- The AvailInfo type
-- | Records what things are "available", i.e. in scope
data
AvailInfo
=
Avail
Name
-- ^ An ordinary identifier in scope
|
AvailTC
Name
[
Name
]
-- ^ A type or class in scope. Parameters:
--
-- 1) The name of the type or class
-- 2) The available pieces of type or class.
--
-- The AvailTC Invariant:
-- * If the type or class is itself
-- to be in scope, it must be
-- *first* in this list. Thus,
-- typically: @AvailTC Eq [Eq, ==, \/=]@
deriving
(
Eq
)
-- Equality used when deciding if the
-- interface has changed
-- | A collection of 'AvailInfo' - several things that are \"available\"
type
Avails
=
[
AvailInfo
]
-- | Compare lexicographically
stableAvailCmp
::
AvailInfo
->
AvailInfo
->
Ordering
stableAvailCmp
(
Avail
n1
)
(
Avail
n2
)
=
n1
`
stableNameCmp
`
n2
stableAvailCmp
(
Avail
{})
(
AvailTC
{})
=
LT
stableAvailCmp
(
AvailTC
n
ns
)
(
AvailTC
m
ms
)
=
(
n
`
stableNameCmp
`
m
)
`
thenCmp
`
(
cmpList
stableNameCmp
ns
ms
)
stableAvailCmp
(
AvailTC
{})
(
Avail
{})
=
GT
-- -----------------------------------------------------------------------------
-- Operations on AvailInfo
availsToNameSet
::
[
AvailInfo
]
->
NameSet
availsToNameSet
avails
=
foldr
add
emptyNameSet
avails
where
add
avail
set
=
addListToNameSet
set
(
availNames
avail
)
availsToNameEnv
::
[
AvailInfo
]
->
NameEnv
AvailInfo
availsToNameEnv
avails
=
foldr
add
emptyNameEnv
avails
where
add
avail
env
=
extendNameEnvList
env
(
zip
(
availNames
avail
)
(
repeat
avail
))
-- | Just the main name made available, i.e. not the available pieces
-- of type or class brought into scope by the 'GenAvailInfo'
availName
::
AvailInfo
->
Name
availName
(
Avail
n
)
=
n
availName
(
AvailTC
n
_
)
=
n
-- | All names made available by the availability information
availNames
::
AvailInfo
->
[
Name
]
availNames
(
Avail
n
)
=
[
n
]
availNames
(
AvailTC
_
ns
)
=
ns
-- | make a 'GlobalRdrEnv' where all the elements point to the same
-- Provenance (useful for "hiding" imports, or imports with
-- no details).
gresFromAvails
::
Provenance
->
[
AvailInfo
]
->
[
GlobalRdrElt
]
gresFromAvails
prov
avails
=
concatMap
(
gresFromAvail
(
const
prov
))
avails
gresFromAvail
::
(
Name
->
Provenance
)
->
AvailInfo
->
[
GlobalRdrElt
]
gresFromAvail
prov_fn
avail
=
[
GRE
{
gre_name
=
n
,
gre_par
=
parent
n
avail
,
gre_prov
=
prov_fn
n
}
|
n
<-
availNames
avail
]
where
parent
_
(
Avail
_
)
=
NoParent
parent
n
(
AvailTC
m
_
)
|
n
==
m
=
NoParent
|
otherwise
=
ParentIs
m
-- -----------------------------------------------------------------------------
-- Printing
instance
Outputable
AvailInfo
where
ppr
=
pprAvail
pprAvail
::
AvailInfo
->
SDoc
pprAvail
(
Avail
n
)
=
ppr
n
pprAvail
(
AvailTC
n
ns
)
=
ppr
n
<>
braces
(
hsep
(
punctuate
comma
(
map
ppr
ns
)))
compiler/deSugar/Desugar.lhs
View file @
94e7c6bf
...
...
@@ -16,6 +16,7 @@ import TcRnTypes
import MkIface
import Id
import Name
import Avail
import CoreSyn
import CoreSubst
import PprCore
...
...
compiler/ghc.cabal.in
View file @
94e7c6bf
...
...
@@ -146,6 +146,7 @@ Library
vectorise
Exposed-Modules:
Avail
BasicTypes
DataCon
Demand
...
...
compiler/iface/BinIface.hs
View file @
94e7c6bf
...
...
@@ -21,6 +21,7 @@ import Annotations
import
IfaceSyn
import
Module
import
Name
import
Avail
import
VarEnv
import
DynFlags
import
UniqFM
...
...
compiler/iface/IfaceEnv.lhs
View file @
94e7c6bf
...
...
@@ -27,6 +27,7 @@ import Type
import DataCon
import Var
import Name
import Avail
import PrelNames
import Module
import UniqFM
...
...
compiler/iface/LoadIface.lhs
View file @
94e7c6bf
...
...
@@ -43,6 +43,7 @@ import InstEnv
import FamInstEnv
import Name
import NameEnv
import Avail
import Module
import Maybes
import ErrUtils
...
...
compiler/iface/MkIface.lhs
View file @
94e7c6bf
...
...
@@ -75,6 +75,7 @@ import VarEnv
import VarSet
import Var
import Name
import Avail
import RdrName
import NameEnv
import NameSet
...
...
compiler/main/GHC.hs
View file @
94e7c6bf
...
...
@@ -265,6 +265,7 @@ import TyCon
import
Class
import
DataCon
import
Name
hiding
(
varName
)
import
Avail
import
InstEnv
import
FamInstEnv
import
SrcLoc
...
...
@@ -276,8 +277,7 @@ import HscTypes
import
DynFlags
import
StaticFlagParser
import
qualified
StaticFlags
import
SysTools
(
initSysTools
,
cleanTempFiles
,
cleanTempDirs
)
import
SysTools
import
Annotations
import
Module
import
UniqFM
...
...
compiler/main/HscTypes.lhs
View file @
94e7c6bf
...
...
@@ -74,9 +74,7 @@ module HscTypes (
WhetherHasOrphans, IsBootInterface, Usage(..),
Dependencies(..), noDependencies,
NameCache(..), OrigNameCache, OrigIParamCache,
Avails, availsToNameSet, availsToNameEnv, availName, availNames,
AvailInfo(..), gresFromAvails, gresFromAvail,
IfaceExport, stableAvailCmp,
IfaceExport,
-- * Warnings
Warnings(..), WarningTxt(..), plusWarns,
...
...
@@ -116,6 +114,7 @@ import {-# SOURCE #-} InteractiveEval ( Resume )
import HsSyn
import RdrName
import Name
import Avail
import NameEnv
import NameSet
import Module
...
...
@@ -695,6 +694,9 @@ data ModIface
-- See Note [RnNames . Trust Own Package]
}
-- | The original names declared of a certain module that are exported
type IfaceExport = AvailInfo
-- | The 'ModDetails' is essentially a cache for information in the 'ModIface'
-- for home modules only. Information relating to packages will be loaded into
-- global environments in 'ExternalPackageState'.
...
...
@@ -1473,82 +1475,6 @@ plusWarns _ (WarnAll t) = WarnAll t
plusWarns (WarnAll t) _ = WarnAll t
plusWarns (WarnSome v1) (WarnSome v2) = WarnSome (v1 ++ v2)
\end{code}
\begin{code}
-- | A collection of 'AvailInfo' - several things that are \"available\"
type Avails = [AvailInfo]
-- | Records what things are "available", i.e. in scope
data AvailInfo = Avail Name -- ^ An ordinary identifier in scope
| AvailTC Name
[Name] -- ^ A type or class in scope. Parameters:
--
-- 1) The name of the type or class
-- 2) The available pieces of type or class.
--
-- The AvailTC Invariant:
-- * If the type or class is itself
-- to be in scope, it must be *first* in this list.
-- Thus, typically: @AvailTC Eq [Eq, ==, \/=]@
deriving( Eq )
-- Equality used when deciding if the interface has changed
-- | The original names declared of a certain module that are exported
type IfaceExport = AvailInfo
availsToNameSet :: [AvailInfo] -> NameSet
availsToNameSet avails = foldr add emptyNameSet avails
where add avail set = addListToNameSet set (availNames avail)
availsToNameEnv :: [AvailInfo] -> NameEnv AvailInfo
availsToNameEnv avails = foldr add emptyNameEnv avails
where add avail env = extendNameEnvList env
(zip (availNames avail) (repeat avail))
-- | Just the main name made available, i.e. not the available pieces
-- of type or class brought into scope by the 'GenAvailInfo'
availName :: AvailInfo -> Name
availName (Avail n) = n
availName (AvailTC n _) = n
-- | All names made available by the availability information
availNames :: AvailInfo -> [Name]
availNames (Avail n) = [n]
availNames (AvailTC _ ns) = ns
-- | make a 'GlobalRdrEnv' where all the elements point to the same
-- import declaration (useful for "hiding" imports, or imports with
-- no details).
gresFromAvails :: Provenance -> [AvailInfo] -> [GlobalRdrElt]
gresFromAvails prov avails
= concatMap (gresFromAvail (const prov)) avails
gresFromAvail :: (Name -> Provenance) -> AvailInfo -> [GlobalRdrElt]
gresFromAvail prov_fn avail
= [ GRE {gre_name = n,
gre_par = parent n avail,
gre_prov = prov_fn n}
| n <- availNames avail ]
where
parent _ (Avail _) = NoParent
parent n (AvailTC m _) | n == m = NoParent
| otherwise = ParentIs m
instance Outputable AvailInfo where
ppr = pprAvail
pprAvail :: AvailInfo -> SDoc
pprAvail (Avail n) = ppr n
pprAvail (AvailTC n ns) = ppr n <> braces (hsep (punctuate comma (map ppr ns)))
stableAvailCmp :: AvailInfo -> AvailInfo -> Ordering
-- Compare lexicographically
stableAvailCmp (Avail n1) (Avail n2) = n1 `stableNameCmp` n2
stableAvailCmp (Avail {}) (AvailTC {}) = LT
stableAvailCmp (AvailTC n ns) (AvailTC m ms) = (n `stableNameCmp` m) `thenCmp`
(cmpList stableNameCmp ns ms)
stableAvailCmp (AvailTC {}) (Avail {}) = GT
\end{code}
\begin{code}
-- | Creates cached lookup for the 'mi_fix_fn' field of 'ModIface'
...
...
compiler/main/InteractiveEval.hs
View file @
94e7c6bf
...
...
@@ -49,6 +49,7 @@ import Var
import
Id
import
Name
hiding
(
varName
)
import
NameSet
import
Avail
import
RdrName
import
PrelNames
(
pRELUDE
)
import
VarSet
...
...
compiler/main/TidyPgm.lhs
View file @
94e7c6bf
...
...
@@ -31,8 +31,9 @@ import Demand
import BasicTypes
import Name hiding (varName)
import NameSet
import IfaceEnv
import NameEnv
import Avail
import IfaceEnv
import TcType
import DataCon
import TyCon
...
...
compiler/prelude/PrelInfo.lhs
View file @
94e7c6bf
...
...
@@ -22,21 +22,20 @@ module PrelInfo (
#include "HsVersions.h"
import PrelNames ( basicKnownKeyNames,
hasKey, charDataConKey, intDataConKey,
numericClassKeys, standardClassKeys )
import PrelNames
import PrelRules
import PrimOp ( PrimOp, allThePrimOps, primOpTag, maxPrimOpTag )
import DataCon ( DataCon )
import Id ( Id, idName )
import MkId -- All of it, for re-export
import TysPrim ( primTyCons )
import TysWiredIn ( wiredInTyCons )
import HscTypes ( TyThing(..), implicitTyThings, AvailInfo(..), IfaceExport )
import Class ( Class, classKey )
import Type ( funTyCon )
import TyCon ( tyConName )
import Util ( isIn )
import Avail
import PrimOp
import DataCon
import Id
import MkId
import TysPrim
import TysWiredIn
import HscTypes
import Class
import Type
import TyCon
import Util
import Data.Array
\end{code}
...
...
compiler/rename/RnBinds.lhs
View file @
94e7c6bf
...
...
@@ -29,16 +29,13 @@ import HsSyn
import RnHsSyn
import TcRnMonad
import RnTypes ( rnIPName, rnHsSigType, rnLHsType, checkPrecMatch )
import RnPat (rnPats, rnBindPat,
NameMaker, localRecNameMaker, topRecNameMaker, applyNameMaker
)
import RnPat
import RnEnv
import DynFlags
import Name
import NameEnv
import NameSet
import RdrName
( RdrName, rdrNameOcc )
import RdrName
( RdrName, rdrNameOcc )
import SrcLoc
import ListSetOps ( findDupsEq )
import BasicTypes ( RecFlag(..) )
...
...
compiler/rename/RnEnv.lhs
View file @
94e7c6bf
...
...
@@ -36,17 +36,18 @@ module RnEnv (
#include "HsVersions.h"
import LoadIface ( loadInterfaceForName, loadSrcInterface )
import IfaceEnv
( lookupOrig, newGlobalBinder, updNameCache, extendNameCache )
import IfaceEnv
import HsSyn
import RdrHsSyn ( extractHsTyRdrTyVars )
import RdrName
import HscTypes
( NameCache(..), availNames, ModIface(..), FixItem(..), lookupFixity)
import HscTypes
import TcEnv ( tcLookupDataCon, tcLookupField, isBrackStage )
import TcRnMonad
import Id ( isRecordSelector )
import Name
import NameSet
import NameEnv
import Avail
import Module ( ModuleName, moduleName )
import UniqFM
import DataCon ( dataConFieldLabels )
...
...
compiler/rename/RnNames.lhs
View file @
94e7c6bf
...
...
@@ -25,6 +25,7 @@ import Module
import Name
import NameEnv
import NameSet
import Avail
import HscTypes
import RdrName
import Outputable
...
...
compiler/rename/RnSource.lhs
View file @
94e7c6bf
...
...
@@ -20,11 +20,9 @@ import RdrName
import RdrHsSyn ( extractHsRhoRdrTyVars )
import RnHsSyn
import RnTypes
import RnBinds ( rnTopBindsLHS, rnTopBindsRHS, rnMethodBinds,
renameSigs, mkSigTvFn, makeMiniFixityEnv )
import RnBinds
import RnEnv
import RnNames ( getLocalNonValBinders, extendGlobalRdrEnvRn, lookupTcdName )
import HscTypes ( AvailInfo(..) )
import RnNames
import RnHsDoc ( rnHsDoc, rnMbLHsDoc )
import TcRnMonad
import Kind ( liftedTypeKind )
...
...
@@ -33,9 +31,10 @@ import ForeignCall ( CCallTarget(..) )
import Module
import HscTypes ( Warnings(..), plusWarns )
import Class ( FunDep )
import Name
( Name, nameOccName )
import Name
import NameSet
import NameEnv
import Avail
import Outputable
import Bag
import FastString
...
...
compiler/typecheck/TcRnDriver.lhs
View file @
94e7c6bf
...
...
@@ -66,6 +66,7 @@ import UniqFM
import Name
import NameEnv
import NameSet
import Avail
import TyCon
import SrcLoc
import HscTypes
...
...
compiler/typecheck/TcRnTypes.lhs
View file @
94e7c6bf
...
...
@@ -76,6 +76,7 @@ import RdrName
import Name
import NameEnv
import NameSet
import Avail
import Var
import VarEnv
import Module
...
...
compiler/typecheck/TcTyDecls.lhs
View file @
94e7c6bf
...
...
@@ -26,6 +26,7 @@ import DataCon
import Name
import NameEnv
import NameSet
import Avail
import Digraph
import BasicTypes
import SrcLoc
...
...
Write
Preview
Markdown
is supported
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment