summaryrefslogtreecommitdiff
path: root/compiler/ghci
diff options
context:
space:
mode:
authorSimon Marlow <simonmar@microsoft.com>2006-10-11 20:01:10 +0000
committerSimon Marlow <simonmar@microsoft.com>2006-10-11 20:01:10 +0000
commitab22f4e6456820c1b5169d75f5975a94e61f54ce (patch)
tree44eb4222120653313776566754c006e1deeb77a3 /compiler/ghci
parent6b4592943b799175dec4549882bbf06fa87a0739 (diff)
downloadhaskell-ab22f4e6456820c1b5169d75f5975a94e61f54ce.tar.gz
More import tidying and fixing the stage 2 build
Diffstat (limited to 'compiler/ghci')
-rw-r--r--compiler/ghci/ByteCodeAsm.lhs23
-rw-r--r--compiler/ghci/ByteCodeFFI.lhs18
-rw-r--r--compiler/ghci/ByteCodeGen.lhs70
-rw-r--r--compiler/ghci/ByteCodeInstr.lhs21
-rw-r--r--compiler/ghci/ByteCodeItbls.lhs11
-rw-r--r--compiler/ghci/ByteCodeLink.lhs24
-rw-r--r--compiler/ghci/InteractiveUI.hs64
-rw-r--r--compiler/ghci/Linker.lhs60
-rw-r--r--compiler/ghci/ObjLink.lhs9
9 files changed, 137 insertions, 163 deletions
diff --git a/compiler/ghci/ByteCodeAsm.lhs b/compiler/ghci/ByteCodeAsm.lhs
index e332413dae..e1346a9c6e 100644
--- a/compiler/ghci/ByteCodeAsm.lhs
+++ b/compiler/ghci/ByteCodeAsm.lhs
@@ -1,7 +1,8 @@
%
-% (c) The University of Glasgow 2002
+% (c) The University of Glasgow 2002-2006
%
-\section[ByteCodeLink]{Bytecode assembler and linker}
+
+ByteCodeLink: Bytecode assembler and linker
\begin{code}
{-# OPTIONS -optc-DNON_POSIX_SOURCE #-}
@@ -18,17 +19,17 @@ module ByteCodeAsm (
#include "HsVersions.h"
import ByteCodeInstr
-import ByteCodeItbls ( ItblEnv, mkITbls )
+import ByteCodeItbls
-import Name ( Name, getName )
+import Name
import NameSet
-import FiniteMap ( addToFM, lookupFM, emptyFM )
-import Literal ( Literal(..) )
-import TyCon ( TyCon )
-import PrimOp ( PrimOp )
-import Constants ( wORD_SIZE )
-import FastString ( FastString(..) )
-import SMRep ( CgRep(..), StgWord )
+import FiniteMap
+import Literal
+import TyCon
+import PrimOp
+import Constants
+import FastString
+import SMRep
import FiniteMap
import Outputable
diff --git a/compiler/ghci/ByteCodeFFI.lhs b/compiler/ghci/ByteCodeFFI.lhs
index ef3fd3e0d6..c5bdc2c61b 100644
--- a/compiler/ghci/ByteCodeFFI.lhs
+++ b/compiler/ghci/ByteCodeFFI.lhs
@@ -1,7 +1,8 @@
%
-% (c) The University of Glasgow 2001
+% (c) The University of Glasgow 2001-2006
%
-\section[ByteCodeGen]{Generate machine-code sequences for foreign import}
+
+ByteCodeGen: Generate machine-code sequences for foreign import
\begin{code}
module ByteCodeFFI ( mkMarshalCode, moan64 ) where
@@ -9,21 +10,20 @@ module ByteCodeFFI ( mkMarshalCode, moan64 ) where
#include "HsVersions.h"
import Outputable
-import SMRep ( CgRep(..), cgRepSizeW )
-import ForeignCall ( CCallConv(..) )
+import SMRep
+import ForeignCall
import Panic
-- DON'T remove apparently unused imports here ..
-- there is ifdeffery below
import Control.Exception ( throwDyn )
-import DATA_BITS ( Bits(..), shiftR, shiftL )
-import Foreign ( newArray )
+import Data.Bits ( Bits(..), shiftR, shiftL )
+import Foreign ( newArray, Ptr )
import Data.List ( mapAccumL )
-import DATA_WORD ( Word8, Word32 )
-import Foreign ( Ptr )
+import Data.Word ( Word8, Word32 )
import System.IO.Unsafe ( unsafePerformIO )
-import IO ( hPutStrLn, stderr )
+import System.IO ( hPutStrLn, stderr )
-- import Debug.Trace ( trace )
\end{code}
diff --git a/compiler/ghci/ByteCodeGen.lhs b/compiler/ghci/ByteCodeGen.lhs
index 40a20cc91e..be068d25c6 100644
--- a/compiler/ghci/ByteCodeGen.lhs
+++ b/compiler/ghci/ByteCodeGen.lhs
@@ -1,7 +1,8 @@
%
-% (c) The University of Glasgow 2002
+% (c) The University of Glasgow 2002-2006
%
-\section[ByteCodeGen]{Generate bytecode from Core}
+
+ByteCodeGen: Generate bytecode from Core
\begin{code}
module ByteCodeGen ( UnlinkedBCO, byteCodeGen, coreExprToBCOs ) where
@@ -9,48 +10,41 @@ module ByteCodeGen ( UnlinkedBCO, byteCodeGen, coreExprToBCOs ) where
#include "HsVersions.h"
import ByteCodeInstr
-import ByteCodeFFI ( mkMarshalCode, moan64 )
-import ByteCodeAsm ( CompiledByteCode(..), UnlinkedBCO,
- assembleBCO, assembleBCOs, iNTERP_STACK_CHECK_THRESH )
-import ByteCodeLink ( lookupStaticPtr )
+import ByteCodeFFI
+import ByteCodeAsm
+import ByteCodeLink
import Outputable
-import Name ( Name, getName, mkSystemVarName )
+import Name
import Id
import FiniteMap
-import ForeignCall ( ForeignCall(..), CCallTarget(..), CCallSpec(..) )
-import HscTypes ( TypeEnv, typeEnvTyCons, typeEnvClasses )
-import CoreUtils ( exprType )
+import ForeignCall
+import HscTypes
+import CoreUtils
import CoreSyn
-import PprCore ( pprCoreExpr )
-import Literal ( Literal(..), literalType )
-import PrimOp ( PrimOp(..) )
-import CoreFVs ( freeVars )
-import Type ( isUnLiftedType, splitTyConApp_maybe )
-import DataCon ( DataCon, dataConTag, fIRST_TAG, dataConTyCon,
- isUnboxedTupleCon, isNullaryRepDataCon, dataConWorkId,
- dataConRepArity )
-import TyCon ( TyCon, tyConFamilySize, isDataTyCon,
- tyConDataCons, isUnboxedTupleTyCon )
-import Class ( Class, classTyCon )
-import Type ( Type, repType, splitFunTys, dropForAlls, pprType )
+import PprCore
+import Literal
+import PrimOp
+import CoreFVs
+import Type
+import DataCon
+import TyCon
+import Class
+import Type
import Util
-import DataCon ( dataConRepArity )
-import Var ( isTyVar )
-import VarSet ( VarSet, varSetElems )
-import TysPrim ( arrayPrimTyCon, mutableArrayPrimTyCon,
- byteArrayPrimTyCon, mutableByteArrayPrimTyCon
- )
-import DynFlags ( DynFlags, DynFlag(..) )
-import ErrUtils ( showPass, dumpIfSet_dyn )
-import Unique ( mkPseudoUniqueE )
-import FastString ( FastString(..), unpackFS )
-import Panic ( GhcException(..) )
-import SMRep ( typeCgRep, arrWordsHdrSize, arrPtrsHdrSize, StgWord,
- CgRep(..), cgRepSizeW, isFollowableArg, idCgRep )
-import Bitmap ( intsToReverseBitmap, mkBitmap )
+import DataCon
+import Var
+import VarSet
+import TysPrim
+import DynFlags
+import ErrUtils
+import Unique
+import FastString
+import Panic
+import SMRep
+import Bitmap
import OrdList
-import Constants ( wORD_SIZE )
+import Constants
import Data.List ( intersperse, sortBy, zip4, zip6, partition )
import Foreign ( Ptr, castPtr, mallocBytes, pokeByteOff, Word8,
@@ -101,7 +95,7 @@ coreExprToBCOs dflags expr
-- create a totally bogus name for the top-level BCO; this
-- should be harmless, since it's never used for anything
let invented_name = mkSystemVarName (mkPseudoUniqueE 0) FSLIT("ExprTopLevel")
- invented_id = mkLocalId invented_name (panic "invented_id's type")
+ invented_id = Id.mkLocalId invented_name (panic "invented_id's type")
(BcM_State final_ctr mallocd, proto_bco)
<- runBc (schemeTopBind (invented_id, freeVars expr))
diff --git a/compiler/ghci/ByteCodeInstr.lhs b/compiler/ghci/ByteCodeInstr.lhs
index 7bd4408fff..b76207e2e7 100644
--- a/compiler/ghci/ByteCodeInstr.lhs
+++ b/compiler/ghci/ByteCodeInstr.lhs
@@ -1,7 +1,7 @@
%
-% (c) The University of Glasgow 2000
+% (c) The University of Glasgow 2000-2006
%
-\section[ByteCodeInstrs]{Bytecode instruction definitions}
+ByteCodeInstrs: Bytecode instruction definitions
\begin{code}
module ByteCodeInstr (
@@ -12,15 +12,16 @@ module ByteCodeInstr (
#include "../includes/MachDeps.h"
import Outputable
-import Name ( Name )
-import Id ( Id )
+import Name
+import Id
import CoreSyn
-import PprCore ( pprCoreExpr, pprCoreAlt )
-import Literal ( Literal )
-import DataCon ( DataCon )
-import VarSet ( VarSet )
-import PrimOp ( PrimOp )
-import SMRep ( StgWord, CgRep )
+import PprCore
+import Literal
+import DataCon
+import VarSet
+import PrimOp
+import SMRep
+
import GHC.Ptr
-- ----------------------------------------------------------------------------
diff --git a/compiler/ghci/ByteCodeItbls.lhs b/compiler/ghci/ByteCodeItbls.lhs
index 6513ff62c5..d990da2198 100644
--- a/compiler/ghci/ByteCodeItbls.lhs
+++ b/compiler/ghci/ByteCodeItbls.lhs
@@ -1,10 +1,9 @@
%
-% (c) The University of Glasgow 2000
+% (c) The University of Glasgow 2000-2006
%
-\section[ByteCodeItbls]{Generate infotables for interpreter-made bytecodes}
+ByteCodeItbls: Generate infotables for interpreter-made bytecodes
\begin{code}
-
{-# OPTIONS -optc-DNON_POSIX_SOURCE #-}
module ByteCodeItbls ( ItblEnv, ItblPtr, mkITbls ) where
@@ -23,14 +22,10 @@ import Util ( lengthIs, listLengthCmp )
import Foreign
import Foreign.C
-import DATA_BITS ( Bits(..), shiftR )
+import Data.Bits ( Bits(..), shiftR )
import GHC.Exts ( Int(I#), addr2Int# )
-#if __GLASGOW_HASKELL__ < 503
-import Ptr ( Ptr(..) )
-#else
import GHC.Ptr ( Ptr(..) )
-#endif
\end{code}
%************************************************************************
diff --git a/compiler/ghci/ByteCodeLink.lhs b/compiler/ghci/ByteCodeLink.lhs
index 6bca06a8f3..fd6654579c 100644
--- a/compiler/ghci/ByteCodeLink.lhs
+++ b/compiler/ghci/ByteCodeLink.lhs
@@ -1,10 +1,9 @@
%
-% (c) The University of Glasgow 2000
+% (c) The University of Glasgow 2000-2006
%
-\section[ByteCodeLink]{Bytecode assembler and linker}
+ByteCodeLink: Bytecode assembler and linker
\begin{code}
-
{-# OPTIONS -optc-DNON_POSIX_SOURCE #-}
module ByteCodeLink (
@@ -15,21 +14,20 @@ module ByteCodeLink (
#include "HsVersions.h"
-import ByteCodeItbls ( ItblEnv, ItblPtr )
-import ByteCodeAsm ( UnlinkedBCO(..), BCOPtr(..), sizeSS, ssElts )
-import ObjLink ( lookupSymbol )
+import ByteCodeItbls
+import ByteCodeAsm
+import ObjLink
-import Name ( Name, nameModule, nameOccName )
+import Name
import NameEnv
-import OccName ( occNameFS )
-import PrimOp ( PrimOp, primOpOcc )
+import OccName
+import PrimOp
import Module
-import PackageConfig ( mainPackageId, packageIdFS )
-import FastString ( FastString(..), unpackFS, zEncodeFS )
-import Panic ( GhcException(..) )
+import PackageConfig
+import FastString
+import Panic
#ifdef DEBUG
-import Name ( isExternalName )
import Outputable
#endif
diff --git a/compiler/ghci/InteractiveUI.hs b/compiler/ghci/InteractiveUI.hs
index 0685168e3d..159a5ce347 100644
--- a/compiler/ghci/InteractiveUI.hs
+++ b/compiler/ghci/InteractiveUI.hs
@@ -3,7 +3,7 @@
--
-- GHC Interactive User Interface
--
--- (c) The GHC Team 2005
+-- (c) The GHC Team 2005-2006
--
-----------------------------------------------------------------------------
module InteractiveUI (
@@ -17,49 +17,40 @@ module InteractiveUI (
import GHC.Exts ( Int(..), Ptr(..), int2Addr# )
import Foreign.StablePtr ( deRefStablePtr, castPtrToStablePtr )
import System.IO.Unsafe ( unsafePerformIO )
-import Var ( Id, globaliseId, idName, idType )
-import HscTypes ( Session(..), InteractiveContext(..), HscEnv(..)
- , extendTypeEnvWithIds )
-import RdrName ( extendLocalRdrEnv, mkRdrUnqual, lookupLocalRdrEnv )
-import NameEnv ( delListFromNameEnv )
-import TcType ( tidyTopType )
-import qualified Id ( setIdType )
-import IdInfo ( GlobalIdDetails(..) )
-import Linker ( HValue, extendLinkEnv, withExtendedLinkEnv,
- initDynLinker )
-import PrelNames ( breakpointJumpName, breakpointCondJumpName )
+import Var
+import HscTypes
+import RdrName
+import NameEnv
+import TcType
+import qualified Id
+import IdInfo
+import PrelNames
#endif
-- The GHC interface
import qualified GHC
-import GHC ( Session, dopt, DynFlag(..), Target(..),
- TargetId(..), DynFlags(..),
- pprModule, Type, Module, ModuleName, SuccessFlag(..),
- TyThing(..), Name, LoadHowMuch(..), Phase,
- GhcException(..), showGhcException,
- CheckedModule(..), SrcLoc )
-import DynFlags ( allFlags )
-import Packages ( PackageState(..) )
-import PackageConfig ( InstalledPackageInfo(..) )
-import UniqFM ( eltsUFM )
+import GHC ( Session, LoadHowMuch(..), Target(..), TargetId(..),
+ Type, Module, ModuleName, TyThing(..), Phase )
+import DynFlags
+import Packages
+import PackageConfig
+import UniqFM
import PprTyThing
import Outputable
--- for createtags (should these come via GHC?)
-import Name ( nameSrcLoc, nameModule, nameOccName )
-import OccName ( pprOccName )
-import SrcLoc ( isGoodSrcLoc, srcLocFile, srcLocLine, srcLocCol )
+-- for createtags
+import Name
+import OccName
+import SrcLoc
-- Other random utilities
-import Digraph ( flattenSCCs )
-import BasicTypes ( failed, successIf )
-import Panic ( panic, installSignalHandlers )
+import Digraph
+import BasicTypes
+import Panic hiding (showException)
import Config
-import StaticFlags ( opt_IgnoreDotGhci )
-import Linker ( showLinkerState, linkPackages )
-import Util ( removeSpaces, handle, global, toArgs,
- looksLikeModuleName, prefixMatch, sortLe,
- joinFileName )
+import StaticFlags
+import Linker
+import Util
#ifndef mingw32_HOST_OS
import System.Posix
@@ -718,7 +709,8 @@ info s = do { let names = words s
filterOutChildren :: [Name] -> [Name]
filterOutChildren names = filter (not . parent_is_there) names
where parent_is_there n
- | Just p <- GHC.nameParent_maybe n = p `elem` names
+-- | Just p <- GHC.nameParent_maybe n = p `elem` names
+-- ToDo!!
| otherwise = False
pprInfo exts (thing, fixity, insts)
@@ -864,7 +856,7 @@ checkModule m = do
case result of
Nothing -> io $ putStrLn "Nothing"
Just r -> io $ putStrLn (showSDoc (
- case checkedModuleInfo r of
+ case GHC.checkedModuleInfo r of
Just cm | Just scope <- GHC.modInfoTopLevelScope cm ->
let
(local,global) = partition ((== modl) . GHC.moduleName . GHC.nameModule) scope
diff --git a/compiler/ghci/Linker.lhs b/compiler/ghci/Linker.lhs
index 976fe92a88..819e620356 100644
--- a/compiler/ghci/Linker.lhs
+++ b/compiler/ghci/Linker.lhs
@@ -1,5 +1,5 @@
%
-% (c) The University of Glasgow 2005
+% (c) The University of Glasgow 2005-2006
%
-- --------------------------------------
@@ -12,7 +12,6 @@ necessary.
\begin{code}
-
{-# OPTIONS -optc-DNON_POSIX_SOURCE -#include "Linker.h" #-}
module Linker ( HValue, showLinkerState,
@@ -23,48 +22,43 @@ module Linker ( HValue, showLinkerState,
#include "HsVersions.h"
-import ObjLink ( loadDLL, loadObj, unloadObj, resolveObjs, initObjLinker )
-import ByteCodeLink ( HValue, ClosureEnv, extendClosureEnv, linkBCO )
-import ByteCodeItbls ( ItblEnv )
-import ByteCodeAsm ( CompiledByteCode(..), bcoFreeNames, UnlinkedBCO(..))
+import ObjLink
+import ByteCodeLink
+import ByteCodeItbls
+import ByteCodeAsm
import Packages
-import DriverPhases ( isObjectFilename, isDynLibFilename )
-import Finder ( findHomeModule, findObjectLinkableMaybe,
- FindResult(..) )
+import DriverPhases
+import Finder
import HscTypes
-import Name ( Name, nameModule, isExternalName, isWiredInName )
+import Name
import NameEnv
-import NameSet ( nameSetToList )
-import UniqFM ( lookupUFM )
+import NameSet
+import UniqFM
import Module
-import ListSetOps ( minusList )
-import DynFlags ( DynFlags(..), getOpts )
-import BasicTypes ( SuccessFlag(..), succeeded, failed )
+import ListSetOps
+import DynFlags
+import BasicTypes
import Outputable
-import PackageConfig ( rtsPackageId )
-import Panic ( GhcException(..) )
-import Util ( zipLazy, global, joinFileExt, joinFileName,
- replaceFilenameSuffix )
-import StaticFlags ( v_Ld_inputs, v_Build_tag )
-import ErrUtils ( debugTraceMsg, mkLocMessage )
-import DriverPhases ( phaseInputExt, Phase(..) )
-import SrcLoc ( SrcSpan )
+import PackageConfig
+import Panic
+import Util
+import StaticFlags
+import ErrUtils
+import DriverPhases
+import SrcLoc
-- Standard libraries
-import Control.Monad ( when, filterM, foldM )
+import Control.Monad
-import Data.IORef ( IORef, readIORef, writeIORef, modifyIORef )
-import Data.List ( partition, nub )
+import Data.IORef
+import Data.List
-import System.IO ( putStr, putStrLn, hPutStrLn, stderr, fixIO )
-import System.Directory ( doesFileExist )
+import System.IO
+import System.Directory
-import Control.Exception ( block, throwDyn, bracket )
-import Maybe ( fromJust )
-#ifdef DEBUG
-import Maybe ( isJust )
-#endif
+import Control.Exception
+import Data.Maybe
#if __GLASGOW_HASKELL__ >= 503
import GHC.IOBase ( IO(..) )
diff --git a/compiler/ghci/ObjLink.lhs b/compiler/ghci/ObjLink.lhs
index 5988165886..f46532fbad 100644
--- a/compiler/ghci/ObjLink.lhs
+++ b/compiler/ghci/ObjLink.lhs
@@ -1,5 +1,5 @@
%
-% (c) The University of Glasgow, 2000
+% (c) The University of Glasgow, 2000-2006
%
-- ---------------------------------------------------------------------------
@@ -22,15 +22,14 @@ module ObjLink (
resolveObjs -- :: IO SuccessFlag
) where
-import Monad ( when )
-
-import Foreign.C
-import Foreign ( nullPtr )
import Panic ( panic )
import BasicTypes ( SuccessFlag, successIf )
import Config ( cLeadingUnderscore )
import Outputable
+import Control.Monad ( when )
+import Foreign.C
+import Foreign ( nullPtr )
import GHC.Exts ( Ptr(..), unsafeCoerce# )
-- ---------------------------------------------------------------------------