{-# LANGUAGE CPP #-} {------------------------------------------------------------------------------- Copyright: Bernie Pope 2004 Module: CmdLine Description: The Baskell interpreter command line. Primary Authors: Bernie Pope Notes: Will use GNU readline if it is available. -------------------------------------------------------------------------------} {- This file is part of baskell. baskell is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 of the License, or (at your option) any later version. baskell is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with baskell; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} module CmdLine (Command (..) , getCommand , initializeCmdLine ) where import Parser (expParser) import AST (Exp) import Data.Char(isSpace) import Text.ParserCombinators.Parsec (ParseError , runParser , (<|>) , eof ) import ParserUtils (Parser , word , singleQuoted , colon ) #ifdef READLINE import qualified System.Console.Readline as Readline (readline , addHistory , initialize ) #endif import Lexer (lexer) -------------------------------------------------------------------------------- data Command = Load FilePath | Quit | Browse | Eval Exp | Type Exp | Help #ifdef DEBUG | ShowAST | ShowDepend #endif -- read some input from the user -- parse the input and return the corresponding command getCommand :: IO Command getCommand = do input <- readline "baskell> " case input of Nothing -> return Quit Just line -> if all isSpace line then getCommand else do addHistory line case parseCommandLine line of Left e -> do putStrLn $ "Parse error: " ++ show e putStrLn $ ":h for help, :q to quit" getCommand Right cmd -> return cmd parseCommandLine :: String -> Either ParseError Command parseCommandLine input = runParser commandLineParser () src (lexer src input) where src = "baskell command line" -- a command line is either a colon-prefixed command -- or an expression to evaluate commandLineParser :: Parser Command commandLineParser = do cmd <- colonCommand <|> evalCommand eof return cmd colonCommand :: Parser Command colonCommand = do colon cmd <- word case cmd of "q" -> return Quit "h" -> return Help "b" -> return Browse "l" -> do fileName <- singleQuoted return $ Load fileName "t" -> do exp <- expParser return $ Type exp #ifdef DEBUG "ast" -> return ShowAST "depend" -> return ShowDepend #endif other -> fail $ "unknown command: " ++ show cmd evalCommand :: Parser Command evalCommand = do exp <- expParser return $ Eval exp -------------------------------------------------------------------------------- -- optional support for GNU Readline initializeCmdLine :: IO () initializeCmdLine #ifdef READLINE = Readline.initialize #else = return () #endif readline :: String -> IO (Maybe String) readline prompt #ifdef READLINE = Readline.readline prompt #else = do putStr prompt input <- getLine return $ Just input #endif addHistory :: String -> IO () addHistory str #ifdef READLINE = Readline.addHistory str #else = return () #endif