Skip to content
GitLab
Projects
Groups
Snippets
/
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Glasgow Haskell Compiler
GHC
Commits
f05dbea1
Commit
f05dbea1
authored
Dec 15, 2000
by
sewardj
Browse files
[project @ 2000-12-15 17:38:45 by sewardj]
temp hack to make contents disappear
parent
ba86f432
Changes
1
Hide whitespace changes
Inline
Side-by-side
ghc/compiler/ghci/StgInterp.lhs
View file @
f05dbea1
...
...
@@ -48,6 +48,8 @@ module StgInterp (
#include "HsVersions.h"
import Linker
import Id ( Id, idPrimRep )
import Outputable
...
...
@@ -65,7 +67,7 @@ import Util
import UniqFM
import UniqSet
import {-# SOURCE #-} MCI_make_constr
--
import {-# SOURCE #-} MCI_make_constr
import FastString
import GlaExts ( Int(..) )
...
...
@@ -94,6 +96,26 @@ import PrelGHC --( unsafeCoerce#, dataToTag#,
import PrelAddr ( Addr(..) )
import PrelFloat ( Float(..), Double(..) )
#if 1
interp = panic "interp"
stgExprToInterpSyn = panic "stgExprToInterpSyn"
stgBindsToInterpSyn = panic "stgBindsToInterpSyn"
iExprToHValue = panic "iExprToHValue"
linkIModules = panic "linkIModules"
filterNameMap = panic "filterNameMap"
type ItblEnv = FiniteMap Name (Ptr StgInfoTable)
type ClosureEnv = FiniteMap Name HValue
data StgInfoTable = StgInfoTable {
ptrs :: Word16,
nptrs :: Word16,
srtlen :: Word16,
tipe :: Word16,
code0, code1, code2, code3, code4, code5, code6, code7 :: Word8
}
#else
-- ---------------------------------------------------------------------------
-- Environments needed by the linker
-- ---------------------------------------------------------------------------
...
...
@@ -180,8 +202,6 @@ conapp2expr ie dcon args
in
rearranged
foreign label "PrelBase_Izh_con_info" prelbase_Izh_con_info :: Addr
-- Handle most common cases specially; do the rest with a generic
-- mechanism (deferred till later :)
mkConApp :: Name -> [Rep] -> [UnlinkedIExpr] -> UnlinkedIExpr
...
...
@@ -1399,5 +1419,7 @@ load addr = do x <- peek addr
-----------------------------------------------------------------------------q
foreign import "strncpy" strncpy :: Ptr a -> ByteArray# -> CInt -> IO ()
#endif
\end{code}
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new 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