Skip to content
Snippets Groups Projects
Commit 094b0ead authored by Simon Marlow's avatar Simon Marlow
Browse files

[project @ 2000-11-07 16:03:38 by simonmar]

Fix compilation with 4.08.1
parent 388e2516
No related merge requests found
......@@ -12,8 +12,7 @@ module CmLink ( Linkable(..), Unlinked(..),
PersistentLinkerState{-abstractly!-}, emptyPLS )
where
import StgInterp ( linkIModules, ClosureEnv, ItblEnv )
import Linker ( loadObj, resolveObjs )
import Interpreter
import CmStaticInfo ( PackageConfigInfo )
import Module ( ModuleName, PackageName )
import InterpSyn ( UnlinkedIBind, HValue, binder )
......
......@@ -23,7 +23,7 @@ import CmLink ( PersistentLinkerState, emptyPLS, Linkable(..),
link, LinkResult(..),
filterModuleLinkables, modname_of_linkable,
is_package_linkable )
import InterpSyn ( HValue )
import Interpreter ( HValue )
import CmSummarise ( summarise, ModSummary(..),
name_of_summary, deps_of_summary,
mimp_name, ms_get_imports )
......
......@@ -46,10 +46,7 @@ import UniqSupply ( mkSplitUniqSupply )
import Bag ( emptyBag )
import Outputable
#ifdef GHCI
import StgInterp ( stgToInterpSyn, ItblEnv )
import InterpSyn ( UnlinkedIBind )
#endif
import Interpreter
import HscStats ( ppSourceStats )
import HscTypes ( ModDetails, ModIface(..), PersistentCompilerState(..),
PersistentRenamerState(..), ModuleLocation(..),
......
-----------------------------------------------------------------------------
-- $Id: Interpreter.hs,v 1.1 2000/11/07 16:03:38 simonmar Exp $
--
-- Interpreter subsystem wrapper
--
-- (c) The University of Glasgow 2000
--
-----------------------------------------------------------------------------
module Interpreter (
#ifdef GHCI
module StgInterp,
module InterpSyn,
module Linker
#else
ClosureEnv, ItblEnv,
linkIModules,
stgToInterpSyn,
HValue,
UnlinkedIBinds,
loadObjs, resolveObjs,
#endif
) where
#ifdef GHCI
import StgInterp
import InterpSyn
import Linker
#else
type ClosureEnv = ()
type ItblEnv = ()
linkIModules = error "linkIModules"
stgToInterpSyn = error "linkIModules"
type HValue = ()
type UnlinkedIBinds = ()
loadObjs = error "loadObjs"
resolveObjs = error "loadObjs"
#endif
......@@ -252,7 +252,7 @@ tcModule pcs hst get_fixity this_mod decls unf_env
tc_insts = map iDFunId local_inst_info,
tc_fords = foi_decls ++ foe_decls',
tc_rules = local_rules'
})
}
)
get_binds decls = foldr ThenBinds EmptyBinds [binds | ValD binds <- decls]
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment