Hi,

In attempting to use the lexer to see whether we are within an alternative
layout context:

ALR: True means that we are "Alternative Layout Mode" which happens when we
run the lexer.   The False instances are from when the parser runs (after we
have done our checking).

Prelude Control.Monad.State> flip evalStateT 10 $ do
ALR: True
ALR: True
ALR: True
ALR: True
ALR: True
ALR: True
ALR: True
ALR: True
ALR: False
ALR: False
ALR: False
ALR: False
ALR: False
ALR: False
ALR: False

<interactive>:1:22: Empty 'do' construct

I have a function which tells us if there is layout going on:

activeContext :: P Bool
activeContext = do
  ctxt <- getALRContext
  expc <- getAlrExpectingOCurly
  impt <- implicitTokenPending
  case (ctxt,expc) of
    ([],Nothing) -> return $ False || impt
    _other       -> return $ True

and in InteractiveUI.hs:

we check the lexer state before we get the next token, since we want the
state immediately prior to encountering EOF.

-- #4316
-- lex the input.  If there is an unclosed layout context, request input
checkInputForLayout :: String -> InputT GHCi (Maybe String)
                    -> InputT GHCi (Maybe String)
checkInputForLayout stmt getStmt = do
   dflags' <- getDynFlags
   let dflags = flattenExtensionFlags $
         xopt_set dflags' Opt_AlternativeLayoutRule
   buf <- liftIO $ stringToStringBuffer stmt
   let loc  = mkSrcLoc (fsLit "<interactive>") 1 1
       pstate = Lexer.mkPState dflags buf loc
   case Lexer.unP (goToEnd check) pstate of
     (Lexer.POk _ False) -> return $ Just stmt
     _other              -> do
       st <- lift getGHCiState
       let p = prompt st
       lift $ setGHCiState st{ prompt = "%s| " }
       mb_stmt <- ghciHandle (\ex -> case fromException ex of
                            Just UserInterrupt -> return Nothing
                            _ -> case fromException ex of
                                 Just ghc_e ->
                                   do liftIO (print (ghc_e :: GhcException))
                                      return Nothing
                                 _other -> liftIO (Exception.throwIO ex))
                     getStmt
       lift $ getGHCiState >>= \st->setGHCiState st{ prompt = p }
       -- the recursive call does not recycle parser state
       -- as we use a new string buffer
       case mb_stmt of
         Nothing  -> return Nothing
         Just str -> if str == ""
           then return $ Just stmt
           else checkInputForLayout (stmt++"\n"++str) getStmt
     where lexFinished (L _ Lexer.ITeof) = return True
           lexFinished _                 = return False
           check = do
             actx <- Lexer.activeContext
             eof <- Lexer.lexer lexFinished
             return (actx,eof)
           goToEnd m = do
             (actx,eof) <- m
             if eof then return actx else goToEnd m

Unfortunately, my "activeContext" is not firing on the input at the top of
the post.  SimonM, any pointers?

Vivian
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to