Subversion

Galculator

?curdirlinks? -

Blame information for rev 7

Line No. Rev Author Line
1 1 paulosilva  
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# OPTIONS_GHC -Wall #-}
4  
5 -------------------------------------------------------------------------------
6  
7 {- |
8 Module      :  Galculator.Interpreter
9 Description :  Command line interpreter of Galculator.
10 Copyright   :  (c) Paulo Silva
11 License     :  LGPL
12  
13 Maintainer  :  paufil@di.uminho.pt
14 Stability   :  experimental
15 Portability :  portable
16  
17 -}
18  
19 -------------------------------------------------------------------------------
20  
21 module Galculator.Interpreter (
22  interactiveUI
23  ) where
24  
25 import Control.GalcError
26 import Control.Monad.Error
27 import Control.Monad.Fresh
28 import Control.Monad.Trans
29 import Data.Char( isSpace )
30 import Data.IORef
31 import Data.List
32 import Galculator.RunCommand
33 import Galculator.State
34 import Language.Command.Parser
35 import Language.Command.Syntax
36 import System.Console.Readline
37  
38  
39 -------------------------------------------------------------------------------
40  
41 -- | Sets the interactive environment: initializes the readline library, puts
42 --   the welcome banner and lanches the interactive loop with the initial state.
43 --   At exit resets the readline library.
44 interactiveUI :: IO ()
45 interactiveUI = do
46   initialize
47   setAttemptedCompletionFunction $ Just completeCommand
48   putStrLn galculatorBanner
49   startGalculator interactiveLoop emptyState
50   putStrLn "Leaving Galculator"
51   resetTerminal Nothing
52   return ()
53  
54 -------------------------------------------------------------------------------
55  
56 -- | Initializes a new session with a given state.
57 startGalculator :: FreshT [String] GalcState a -> GalcSt -> IO a
58 startGalculator g state =
59   aux (evalFreshT g (map show ([1..]::[Integer]))) state
60   where aux :: GalcState a -> GalcSt -> IO a
61         aux g' state' = do
62           ref <- newIORef state'
63           unGalcState g' ref
64  
65 -------------------------------------------------------------------------------
66  
67 prompt :: String
68 prompt = "Galculator> "
69  
70 -------------------------------------------------------------------------------
71  
72 interactiveLoop :: FreshT [String] GalcState ()
73 interactiveLoop = runErrorT (interactiveLoop') >> return ()
74  
75 -------------------------------------------------------------------------------
76  
77 interactiveLoop' :: GalcStateT ()
78 interactiveLoop' = do
79   cmd <- liftIO . readline $ prompt
80   exit <- maybe (return False) aux cmd
81   if exit then return () else interactiveLoop'
82   where
83     aux c = if null . removeSpaces $ c
84             then return False
85             else (do
86               liftIO . addHistory $ c
87               runCommand =<< parser c) `catchError` showError
88  
89 -------------------------------------------------------------------------------
90  
91 showError :: GalcError -> GalcStateT Bool
92 7 paulosilva showError = keepGoing . liftIO . putStrLn . (++) "***Galculator error:\n" . show
93 1 paulosilva  
94 -------------------------------------------------------------------------------
95  
96 completeCommand :: String -> Int -> Int -> IO (Maybe (String, [String]))
97 completeCommand str _ _ = do
98   let lst = foldr (\c r -> if str `isPrefixOf` c then c:r else r) [] commands
99   case lst of
100     [] -> return Nothing
101     [x] -> return $ Just (x,[])
102     xs -> return $ Just (getCommonPrefix xs, xs)
103  
104 -------------------------------------------------------------------------------
105 -- Stollen from GHCi
106 getCommonPrefix :: [String] -> String
107 getCommonPrefix [] = ""
108 getCommonPrefix (str:ss) = foldl common str ss
109   where common _ "" = ""
110         common "" _ = ""
111         common (c:cs) (d:ds)
112           | c == d = c : common cs ds
113           | otherwise = ""
114  
115 -------------------------------------------------------------------------------
116 -- Stollen from GHC Utils
117 removeSpaces :: String -> String
118 removeSpaces = reverse . dropWhile isSpace . reverse . dropWhile isSpace
119  
120 -------------------------------------------------------------------------------
121  
122 galculatorBanner :: String
123 galculatorBanner =
124  "   ___    __    _      ___  _   _  _         __   _____  __   ___ \n" ++
125  "  / _ \\  /  \\  | |    / __|| | | || |       /  \\ |_   _|/   \\|    \\\n" ++
126  " / /_\\/ / /\\ \\ | |   | |   | | | || |      / /\\ \\  | |  | | ||    /\n" ++
127  "/ /_\\\\ / ___  \\| |___| |__ | |_| || |___  / ___  \\ | |  | | || |\\ \\\n" ++
128  "\\____//_/   \\_/ \\____|\\___|\\____/  \\____|/_/   \\_/ |_|  \\___/|_|  \\_\\\n\n" ++
129  " Paulo Silva (paufil@di.uminho.pt)\n" ++
130  " Universidade do Minho, Braga, Portugal\n"
131  
132 -------------------------------------------------------------------------------

Theme by Vikram Singh | Powered by WebSVN v2.3.3