diff -rN old-ghc/compiler/ghci/InteractiveUI.hs new-ghc/compiler/ghci/InteractiveUI.hs
160a166
>  "   :{\\n ..lines.. \\n:}\\n       multiline command\n" ++
328c334
<   	     Right hdl -> fileLoop hdl False
---
>   	     Right hdl -> runCommands (fileLoop hdl False)
344c350
<   		  Right hdl -> fileLoop hdl False
---
>   		  Right hdl -> runCommands (fileLoop hdl False)
405,406c411,412
< 	then readlineLoop
< 	else fileLoop stdin show_prompt
---
> 	then runCommands readlineLoop
> 	else runCommands (fileLoop stdin show_prompt)
408c414
<   fileLoop stdin show_prompt
---
>   runCommands (fileLoop stdin show_prompt)
443c449
< fileLoop :: Handle -> Bool -> GHCi ()
---
> fileLoop :: Handle -> Bool -> GHCi (Maybe String)
450,462c456,464
< 	Left e | isEOFError e		   -> return ()
< 	       | InvalidArgument <- etype  -> return ()
< 	       | otherwise		   -> io (ioError e)
< 		where etype = ioeGetErrorType e
< 		-- treat InvalidArgument in the same way as EOF:
< 		-- this can happen if the user closed stdin, or
< 		-- perhaps did getContents which closes stdin at
< 		-- EOF.
< 	Right l -> 
< 	  case removeSpaces l of
<             "" -> fileLoop hdl show_prompt
< 	    l  -> do quit <- runCommands l
<                      if quit then return () else fileLoop hdl show_prompt
---
>         Left e | isEOFError e              -> return Nothing
>                | InvalidArgument <- etype  -> return Nothing
>                | otherwise                 -> io (ioError e)
>                 where etype = ioeGetErrorType e
>                 -- treat InvalidArgument in the same way as EOF:
>                 -- this can happen if the user closed stdin, or
>                 -- perhaps did getContents which closes stdin at
>                 -- EOF.
>         Right l -> return (Just l)
501c503
< readlineLoop :: GHCi ()
---
> readlineLoop :: GHCi (Maybe String)
511,512c513,514
< 		-- readline sometimes puts stdin into blocking mode,
< 		-- so we need to put it back for the IO library
---
>                 -- readline sometimes puts stdin into blocking mode,
>                 -- so we need to put it back for the IO library
515,522c517,520
< 	Nothing -> return ()
< 	Just l  ->
< 	  case removeSpaces l of
< 	    "" -> readlineLoop
< 	    l  -> do
<         	  io (addHistory l)
<   	  	  quit <- runCommands l
<           	  if quit then return () else readlineLoop
---
>         Nothing -> return Nothing
>         Just l  -> do
>                    io (addHistory l)
>                    return (Just l)
525,528c523,537
< runCommands :: String -> GHCi Bool
< runCommands cmd = do
<         q <- ghciHandle handler (doCommand cmd)
<         if q then return True else runNext
---
> queryQueue :: GHCi (Maybe String)
> queryQueue = do
>   st <- getGHCiState
>   case cmdqueue st of
>     []   -> return Nothing
>     c:cs -> do setGHCiState st{ cmdqueue = cs }
>                return (Just c)
> 
> runCommands :: GHCi (Maybe String) -> GHCi ()
> runCommands getCmd = do
>   mb_cmd <- noSpace queryQueue
>   mb_cmd <- maybe (noSpace getCmd) (return . Just) mb_cmd
>   maybe (return ()) 
>         (((bool (return ()) (runCommands getCmd)) =<<)
>           . ghciHandle handler . doCommand) mb_cmd
530,539c539,558
<        runNext = do
<           st <- getGHCiState
<           case cmdqueue st of
<             []   -> return False
<             c:cs -> do setGHCiState st{ cmdqueue = cs }
<                        runCommands c
< 
<        doCommand (':' : cmd) = specialCommand cmd
<        doCommand stmt        = do timeIt $ runStmt stmt GHC.RunToCompletion
<                                   return False
---
>     bool t e b = if b then t else e
>     noSpace q = q >>= maybe (return Nothing)
>                             (\c->case removeSpaces c of 
>                                    ""   -> noSpace q
>                                    ":{" -> multiLineCmd q
>                                    c    -> return (Just c) )
>     multiLineCmd q = do
>       st <- getGHCiState
>       let p = prompt st
>       setGHCiState st{ prompt = "%s| " }
>       mb_cmd <- collectCommand q ""
>       getGHCiState >>= \st->setGHCiState st{ prompt = p }
>       return mb_cmd
>     collectCommand q c = q >>= maybe (return Nothing)
>                                      (\l->if l==":}" 
>                                           then return (Just c) 
>                                           else collectCommand q (c++l))
>     doCommand (':' : cmd) = specialCommand cmd
>     doCommand stmt        = do timeIt $ runStmt stmt GHC.RunToCompletion
>                                return False
