refactor import declaration support (#2362)
[ghc-hetmet.git] / ghc / GhciMonad.hs
1 {-# OPTIONS_GHC -fno-cse -fno-warn-orphans #-}
2 -- -fno-cse is needed for GLOBAL_VAR's to behave properly
3
4 -----------------------------------------------------------------------------
5 --
6 -- Monadery code used in InteractiveUI
7 --
8 -- (c) The GHC Team 2005-2006
9 --
10 -----------------------------------------------------------------------------
11
12 module GhciMonad where
13
14 #include "HsVersions.h"
15
16 import qualified GHC
17 import Outputable       hiding (printForUser, printForUserPartWay)
18 import qualified Outputable
19 import Panic            hiding (showException)
20 import Util
21 import DynFlags
22 import HscTypes hiding (liftIO)
23 import SrcLoc
24 import Module
25 import ObjLink
26 import Linker
27 import StaticFlags
28 import qualified MonadUtils
29
30 import Exception
31 -- import Data.Maybe
32 import Numeric
33 import Data.Array
34 -- import Data.Char
35 import Data.Int         ( Int64 )
36 import Data.IORef
37 -- import Data.List
38 import System.CPUTime
39 import System.Environment
40 import System.IO
41 import Control.Monad as Monad
42 import GHC.Exts
43
44 import System.Console.Haskeline (CompletionFunc, InputT)
45 import qualified System.Console.Haskeline as Haskeline
46 import Control.Monad.Trans as Trans
47
48 -----------------------------------------------------------------------------
49 -- GHCi monad
50
51 type Command = (String, String -> InputT GHCi Bool, CompletionFunc GHCi)
52
53 data GHCiState = GHCiState
54      { 
55         progname       :: String,
56         args           :: [String],
57         prompt         :: String,
58         editor         :: String,
59         stop           :: String,
60         options        :: [GHCiOption],
61         prelude        :: GHC.Module,
62         break_ctr      :: !Int,
63         breaks         :: ![(Int, BreakLocation)],
64         tickarrays     :: ModuleEnv TickArray,
65                 -- tickarrays caches the TickArray for loaded modules,
66                 -- so that we don't rebuild it each time the user sets
67                 -- a breakpoint.
68         -- ":" at the GHCi prompt repeats the last command, so we
69         -- remember is here:
70         last_command   :: Maybe Command,
71         cmdqueue       :: [String],
72         remembered_ctx :: [CtxtCmd],
73              -- we remember the :module commands between :loads, so that
74              -- on a :reload we can replay them.  See bugs #2049,
75              -- \#1873, #1360. Previously we tried to remember modules that
76              -- were supposed to be in the context but currently had errors,
77              -- but this was complicated.  Just replaying the :module commands
78              -- seems to be the right thing.
79         ghc_e :: Bool -- True if this is 'ghc -e' (or runghc)
80      }
81
82 data CtxtCmd
83   = SetContext [String] [String]
84   | AddModules [String] [String]
85   | RemModules [String] [String]
86   | Import     String
87
88 type TickArray = Array Int [(BreakIndex,SrcSpan)]
89
90 data GHCiOption 
91         = ShowTiming            -- show time/allocs after evaluation
92         | ShowType              -- show the type of expressions
93         | RevertCAFs            -- revert CAFs after every evaluation
94         deriving Eq
95
96 data BreakLocation
97    = BreakLocation
98    { breakModule :: !GHC.Module
99    , breakLoc    :: !SrcSpan
100    , breakTick   :: {-# UNPACK #-} !Int
101    , onBreakCmd  :: String
102    } 
103
104 instance Eq BreakLocation where
105   loc1 == loc2 = breakModule loc1 == breakModule loc2 &&
106                  breakTick loc1   == breakTick loc2
107
108 prettyLocations :: [(Int, BreakLocation)] -> SDoc
109 prettyLocations []   = text "No active breakpoints." 
110 prettyLocations locs = vcat $ map (\(i, loc) -> brackets (int i) <+> ppr loc) $ reverse $ locs
111
112 instance Outputable BreakLocation where
113    ppr loc = (ppr $ breakModule loc) <+> ppr (breakLoc loc) <+>
114                 if null (onBreakCmd loc)
115                    then empty
116                    else doubleQuotes (text (onBreakCmd loc))
117
118 recordBreak :: BreakLocation -> GHCi (Bool{- was already present -}, Int)
119 recordBreak brkLoc = do
120    st <- getGHCiState
121    let oldActiveBreaks = breaks st 
122    -- don't store the same break point twice
123    case [ nm | (nm, loc) <- oldActiveBreaks, loc == brkLoc ] of
124      (nm:_) -> return (True, nm)
125      [] -> do
126       let oldCounter = break_ctr st
127           newCounter = oldCounter + 1
128       setGHCiState $ st { break_ctr = newCounter,
129                           breaks = (oldCounter, brkLoc) : oldActiveBreaks
130                         }
131       return (False, oldCounter)
132
133 newtype GHCi a = GHCi { unGHCi :: IORef GHCiState -> Ghc a }
134
135 reflectGHCi :: (Session, IORef GHCiState) -> GHCi a -> IO a
136 reflectGHCi (s, gs) m = unGhc (unGHCi m gs) s
137
138 reifyGHCi :: ((Session, IORef GHCiState) -> IO a) -> GHCi a
139 reifyGHCi f = GHCi f'
140   where
141     -- f' :: IORef GHCiState -> Ghc a
142     f' gs = reifyGhc (f'' gs)
143     -- f'' :: IORef GHCiState -> Session -> IO a
144     f'' gs s = f (s, gs)
145
146 startGHCi :: GHCi a -> GHCiState -> Ghc a
147 startGHCi g state = do ref <- liftIO $ newIORef state; unGHCi g ref
148
149 instance Monad GHCi where
150   (GHCi m) >>= k  =  GHCi $ \s -> m s >>= \a -> unGHCi (k a) s
151   return a  = GHCi $ \_ -> return a
152
153 instance Functor GHCi where
154     fmap f m = m >>= return . f
155
156 ghciHandleGhcException :: (GhcException -> GHCi a) -> GHCi a -> GHCi a
157 ghciHandleGhcException = handleGhcException
158
159 getGHCiState :: GHCi GHCiState
160 getGHCiState   = GHCi $ \r -> liftIO $ readIORef r
161 setGHCiState :: GHCiState -> GHCi ()
162 setGHCiState s = GHCi $ \r -> liftIO $ writeIORef r s
163
164 liftGhc :: Ghc a -> GHCi a
165 liftGhc m = GHCi $ \_ -> m
166
167 instance MonadUtils.MonadIO GHCi where
168   liftIO = liftGhc . MonadUtils.liftIO
169
170 instance Trans.MonadIO Ghc where
171   liftIO = MonadUtils.liftIO
172
173 instance GhcMonad GHCi where
174   setSession s' = liftGhc $ setSession s'
175   getSession    = liftGhc $ getSession
176
177 instance GhcMonad (InputT GHCi) where
178   setSession = lift . setSession
179   getSession = lift getSession
180
181 instance MonadUtils.MonadIO (InputT GHCi) where
182   liftIO = Trans.liftIO
183
184 instance WarnLogMonad (InputT GHCi) where
185   setWarnings = lift . setWarnings
186   getWarnings = lift getWarnings
187
188 instance ExceptionMonad GHCi where
189   gcatch m h = GHCi $ \r -> unGHCi m r `gcatch` (\e -> unGHCi (h e) r)
190   gblock (GHCi m)   = GHCi $ \r -> gblock (m r)
191   gunblock (GHCi m) = GHCi $ \r -> gunblock (m r)
192
193 instance WarnLogMonad GHCi where
194   setWarnings warns = liftGhc $ setWarnings warns
195   getWarnings = liftGhc $ getWarnings
196
197 instance MonadIO GHCi where
198   liftIO = io
199
200 instance Haskeline.MonadException GHCi where
201   catch = gcatch
202   block = gblock
203   unblock = gunblock
204
205 instance ExceptionMonad (InputT GHCi) where
206     gcatch = Haskeline.catch
207     gblock = Haskeline.block
208     gunblock = Haskeline.unblock
209
210 -- for convenience...
211 getPrelude :: GHCi Module
212 getPrelude = getGHCiState >>= return . prelude
213
214 getDynFlags :: GhcMonad m => m DynFlags
215 getDynFlags = do
216   GHC.getSessionDynFlags
217
218 setDynFlags :: DynFlags -> GHCi [PackageId]
219 setDynFlags dflags = do 
220   GHC.setSessionDynFlags dflags
221
222 isOptionSet :: GHCiOption -> GHCi Bool
223 isOptionSet opt
224  = do st <- getGHCiState
225       return (opt `elem` options st)
226
227 setOption :: GHCiOption -> GHCi ()
228 setOption opt
229  = do st <- getGHCiState
230       setGHCiState (st{ options = opt : filter (/= opt) (options st) })
231
232 unsetOption :: GHCiOption -> GHCi ()
233 unsetOption opt
234  = do st <- getGHCiState
235       setGHCiState (st{ options = filter (/= opt) (options st) })
236
237 io :: IO a -> GHCi a
238 io = MonadUtils.liftIO
239
240 printForUser :: GhcMonad m => SDoc -> m ()
241 printForUser doc = do
242   unqual <- GHC.getPrintUnqual
243   MonadUtils.liftIO $ Outputable.printForUser stdout unqual doc
244
245 printForUserPartWay :: SDoc -> GHCi ()
246 printForUserPartWay doc = do
247   unqual <- GHC.getPrintUnqual
248   io $ Outputable.printForUserPartWay stdout opt_PprUserLength unqual doc
249
250 runStmt :: String -> GHC.SingleStep -> GHCi GHC.RunResult
251 runStmt expr step = do
252   st <- getGHCiState
253   reifyGHCi $ \x ->
254     withProgName (progname st) $
255     withArgs (args st) $
256       reflectGHCi x $ do
257         GHC.handleSourceError (\e -> do GHC.printExceptionAndWarnings e
258                                         return GHC.RunFailed) $ do
259           GHC.runStmt expr step
260
261 resume :: (SrcSpan -> Bool) -> GHC.SingleStep -> GHCi GHC.RunResult
262 resume canLogSpan step = do
263   st <- getGHCiState
264   reifyGHCi $ \x ->
265     withProgName (progname st) $
266     withArgs (args st) $
267       reflectGHCi x $ do
268         GHC.resume canLogSpan step
269
270 -- --------------------------------------------------------------------------
271 -- timing & statistics
272
273 timeIt :: InputT GHCi a -> InputT GHCi a
274 timeIt action
275   = do b <- lift $ isOptionSet ShowTiming
276        if not b 
277           then action 
278           else do allocs1 <- liftIO $ getAllocations
279                   time1   <- liftIO $ getCPUTime
280                   a <- action
281                   allocs2 <- liftIO $ getAllocations
282                   time2   <- liftIO $ getCPUTime
283                   liftIO $ printTimes (fromIntegral (allocs2 - allocs1)) 
284                                   (time2 - time1)
285                   return a
286
287 foreign import ccall unsafe "getAllocations" getAllocations :: IO Int64
288         -- defined in ghc/rts/Stats.c
289
290 printTimes :: Integer -> Integer -> IO ()
291 printTimes allocs psecs
292    = do let secs = (fromIntegral psecs / (10^(12::Integer))) :: Float
293             secs_str = showFFloat (Just 2) secs
294         putStrLn (showSDoc (
295                  parens (text (secs_str "") <+> text "secs" <> comma <+> 
296                          text (show allocs) <+> text "bytes")))
297
298 -----------------------------------------------------------------------------
299 -- reverting CAFs
300         
301 revertCAFs :: GHCi ()
302 revertCAFs = do
303   io $ rts_revertCAFs
304   s <- getGHCiState
305   when (not (ghc_e s)) $ io turnOffBuffering
306         -- Have to turn off buffering again, because we just 
307         -- reverted stdout, stderr & stdin to their defaults.
308
309 foreign import ccall "revertCAFs" rts_revertCAFs  :: IO ()  
310         -- Make it "safe", just in case
311
312 -----------------------------------------------------------------------------
313 -- To flush buffers for the *interpreted* computation we need
314 -- to refer to *its* stdout/stderr handles
315
316 GLOBAL_VAR(stdin_ptr,  error "no stdin_ptr",  Ptr ())
317 GLOBAL_VAR(stdout_ptr, error "no stdout_ptr", Ptr ())
318 GLOBAL_VAR(stderr_ptr, error "no stderr_ptr", Ptr ())
319
320 -- After various attempts, I believe this is the least bad way to do
321 -- what we want.  We know look up the address of the static stdin,
322 -- stdout, and stderr closures in the loaded base package, and each
323 -- time we need to refer to them we cast the pointer to a Handle.
324 -- This avoids any problems with the CAF having been reverted, because
325 -- we'll always get the current value.
326 --
327 -- The previous attempt that didn't work was to compile an expression
328 -- like "hSetBuffering stdout NoBuffering" into an expression of type
329 -- IO () and run this expression each time we needed it, but the
330 -- problem is that evaluating the expression might cache the contents
331 -- of the Handle rather than referring to it from its static address
332 -- each time.  There's no safe workaround for this.
333
334 initInterpBuffering :: Ghc ()
335 initInterpBuffering = do -- make sure these are linked
336     dflags <- GHC.getSessionDynFlags
337     liftIO $ do
338       initDynLinker dflags
339
340         -- ToDo: we should really look up these names properly, but
341         -- it's a fiddle and not all the bits are exposed via the GHC
342         -- interface.
343       mb_stdin_ptr  <- ObjLink.lookupSymbol "base_GHCziIOziHandleziFD_stdin_closure"
344       mb_stdout_ptr <- ObjLink.lookupSymbol "base_GHCziIOziHandleziFD_stdout_closure"
345       mb_stderr_ptr <- ObjLink.lookupSymbol "base_GHCziIOziHandleziFD_stderr_closure"
346
347       let f ref (Just ptr) = writeIORef ref ptr
348           f _   Nothing    = panic "interactiveUI:setBuffering2"
349       zipWithM_ f [stdin_ptr,stdout_ptr,stderr_ptr]
350                   [mb_stdin_ptr,mb_stdout_ptr,mb_stderr_ptr]
351
352 flushInterpBuffers :: GHCi ()
353 flushInterpBuffers
354  = io $ do getHandle stdout_ptr >>= hFlush
355            getHandle stderr_ptr >>= hFlush
356
357 turnOffBuffering :: IO ()
358 turnOffBuffering
359  = do hdls <- mapM getHandle [stdin_ptr,stdout_ptr,stderr_ptr]
360       mapM_ (\h -> hSetBuffering h NoBuffering) hdls
361
362 getHandle :: IORef (Ptr ()) -> IO Handle
363 getHandle ref = do
364   (Ptr addr) <- readIORef ref
365   case addrToHValue# addr of (# hval #) -> return (unsafeCoerce# hval)