Forráskód Böngészése

improved intrpreter shell

git-svn-id: https://svn.inf.ethz.ch/svn/lecturers/a2/trunk@6662 8c9fc860-2736-0410-a75d-ab315db34111
felixf 9 éve
szülő
commit
6164c644b0
2 módosított fájl, 138 hozzáadás és 91 törlés
  1. 119 9
      source/InterpreterShell.Mod
  2. 19 82
      source/WMInterpreterShell.Mod

+ 119 - 9
source/InterpreterShell.Mod

@@ -217,6 +217,101 @@ TYPE
 			FOR i :=	 0 TO len-1 DO context.out.Char(Backspace); END;
 		END DeleteStringFromDisplay;
 
+		PROCEDURE ReadCommand(w: Streams.Writer (*VAR command : ARRAY OF CHAR*));
+		VAR
+			ch: CHAR;
+			currentIndex : LONGINT;
+			
+
+			PROCEDURE IsAsciiCharacter(ch : CHAR) : BOOLEAN;
+			BEGIN
+				RETURN ORD(ch) <= 127;
+			END IsAsciiCharacter;
+
+			PROCEDURE IsControlCharacter(ch : CHAR) : BOOLEAN;
+			BEGIN
+				RETURN ORD(ch) < 32;
+			END IsControlCharacter;
+
+			PROCEDURE HandleEscapeSequence;
+			BEGIN
+				ch := context.in.Get();
+				ch := CHR(ORD(ch)+128);
+
+				IF (ch = CursorDown) OR (ch = CursorUp) THEN (* Command History Keys *)
+
+					command[currentIndex+1] := 0X;
+					DeleteStringFromDisplay(command);
+
+					IF ch = CursorUp THEN
+						commandHistory.GetPreviousCommand(command);
+					ELSE
+						commandHistory.GetNextCommand(command);
+					END;
+					currentIndex := Strings.Length(command)-1;
+					IF echo & (command # "") THEN context.out.String(command); context.out.Update; END;
+				ELSE
+					(* ignore escaped character *)
+				END;
+			END HandleEscapeSequence;
+
+		BEGIN
+			command := ""; currentIndex := -1;
+
+			LOOP
+				ch := context.in.Get();
+
+				IF IsAsciiCharacter(ch) THEN
+
+					IF IsControlCharacter(ch) OR (ch = Delete) THEN
+
+						IF (ch = CR) OR (ch = LF) OR (ch = Streams.EOT) OR (context.in.res # Streams.Ok) THEN
+							EXIT
+
+						ELSIF (ch = Backspace) OR (ch = Delete)THEN
+							IF currentIndex >= 0 THEN (* There is a character at the left of the cursor *)
+								command[currentIndex] := 0X;
+								DEC(currentIndex);
+								IF echo THEN
+									context.out.Char(Backspace); context.out.Char(Space); context.out.Char(Backspace); context.out.Update;
+								END;
+							END;
+						ELSIF (ORD(ch) = 03H) THEN
+						(*	IF runner # NIL THEN AosActive.TerminateThis(runner); END; *)
+						ELSIF (ch = EscapeChar1) THEN (* Escape sequence *)
+							IF context.in.Peek() = EscapeChar2 THEN ch := context.in.Get(); HandleEscapeSequence;
+							ELSIF context.in.Peek () = Escape THEN
+								command[currentIndex+1] := 0X;
+								DeleteStringFromDisplay (command); context.out.Update;
+								ch := context.in.Get (); command := ""; currentIndex := -1;
+							END;
+						ELSE
+							(* ignore other control characters *)
+						END;
+
+					ELSE
+						IF currentIndex <= LEN(command) - 2 (* Always need space for 0X *) THEN
+							INC(currentIndex);
+							command[currentIndex] := ch;
+							IF echo THEN context.out.Char(ch); context.out.Update; END;
+						END;
+					END;
+
+				ELSE
+					(* ignore non-ascii characters *)
+				END;
+			END;
+
+			command[currentIndex+1] := 0X;
+
+			IF ch = CR THEN
+				commandHistory.AddCommand(command);
+				IF (context.in.Available() > 0) & (context.in.Peek() = LF) THEN ch := context.in.Get() END;
+				IF echo THEN context.out.Ln; context.out.Update END
+			END;
+			w.String(command);
+		END ReadCommand;
+(*
 		PROCEDURE ReadCommand(w: Streams.Writer);
 		VAR
 			ch: CHAR;
@@ -258,6 +353,7 @@ TYPE
 			command := ""; currentIndex := -1;
 			LOOP
 				ch := context.in.Get();
+				TRACE(ch);
 				IF IsAsciiCharacter(ch) THEN
 
 					IF IsControlCharacter(ch) OR (ch = Delete) THEN
@@ -279,6 +375,7 @@ TYPE
 						(*	IF runner # NIL THEN AosActive.TerminateThis(runner); END; *)
 						ELSIF (ch = EscapeChar1) THEN (* Escape sequence *)
 							IF context.in.Peek() = EscapeChar2 THEN ch := context.in.Get(); HandleEscapeSequence;
+							ELSIF context.in.Peek() = 
 							ELSIF context.in.Peek() = 0DX THEN (* command *)
 								ch := context.in.Get();
 								INC(currentIndex); command[currentIndex] := ch;
@@ -322,6 +419,7 @@ TYPE
 				w.String(command);
 			END;
 		END ReadCommand;
+		*)
 		(*
 		PROCEDURE Parse(VAR cmd: Command; VAR wait: BOOLEAN): LONGINT;
 		VAR sym: SET; pos: LONGINT; c, next: CHAR;
@@ -693,9 +791,11 @@ TYPE
 			stm: SyntaxTree.Statement;
 			diagnostics: Diagnostics.Diagnostics;
 			seq: SyntaxTree.StatementSequence;
+			expression: SyntaxTree.Expression;
 			interpreter: Interpreter.Interpreter;
 			container: Interpreter.Container; scope: Interpreter.Scope; 
 			context: Commands.Context;
+			value: Interpreter.Value;
 
 				PROCEDURE &Init(r: Streams.Reader; diag: Diagnostics.Diagnostics; ctxt: Commands.Context);
 				BEGIN
@@ -705,6 +805,9 @@ TYPE
 				
 			BEGIN{ACTIVE}
 				ASSERT(diagnostics # NIL);
+				context.out.Ln;
+				context.out.String(">");
+				context.out.Update;
 				NEW(scanner,"", r, 0, diagnostics);
 				scanner.SetCase(Scanner.Lowercase);
 				NEW(parser, scanner, diagnostics); (* silent *) 
@@ -716,10 +819,25 @@ TYPE
 				LOOP
 				(*diagnostics.Information("interpreter",Diagnostics.Invalid,Diagnostics.Invalid,"start statement");*)
 				seq := SyntaxTree.NewStatementSequence();
-				IF parser.Statement(seq, NIL) THEN
+				IF parser.Optional(Scanner.Questionmark) THEN
+					expression := parser.Expression();
+					IF interpreter.GetValue(expression, value) THEN
+						value.WriteValue(context.out);
+					ELSE
+						context.out.String("NIL")
+					END;
+					context.out.Ln;
+					context.out.String(">");
+					context.out.Update;
+					WHILE parser.Optional(Scanner.Escape)  DO 
+					END;
+				ELSIF parser.Statement(seq, NIL) THEN
 					(*Printout.Info("executing ", seq);*)
 					interpreter.StatementSequence(seq);
 					context.out.Update;
+					context.out.Ln;
+					context.out.String(">");
+					context.out.Update;
 					WHILE parser.Optional(Scanner.Escape) OR parser.Optional(Scanner.Semicolon) DO 
 						(*TRACE(parser.Token());*)
 					END;
@@ -751,14 +869,6 @@ TYPE
 			
 			(*seq := parser.StatementSequence(NIL);*)
 			WHILE ~close & ~exit & (context.in.res = Streams.Ok) DO
-				IF (prompt # "") THEN
-					context.out.Ln;
-					context.out.String(prompt);
-					FOR i := 0 TO nestingLevel-1 DO
-						context.out.String(NestingLevelIndicator);
-					END;
-					context.out.Update
-				END;
 				s.Clear;
 				ReadCommand(w);w.Char(Escape);w.Ln; w.Update;(*
 				context.out.Ln; context.out.String("------------");

+ 19 - 82
source/WMInterpreterShell.Mod

@@ -26,7 +26,7 @@ CONST
 
 	ReceiveBufferSize = 256;
 
-	Prompt = "";
+	Prompt = "SHELL>";
 
 	Backspace = 08X;
 	ESC = 1BX;
@@ -42,8 +42,7 @@ TYPE
 		pipeOut, pipeIn : Pipes.Pipe;
 
 		(* Terminal window text writer *)
-		w: TextUtilities.TextWriter;
-		r: Texts.TextReader;
+		w : TextUtilities.TextWriter;
 		text : Texts.Text;
 
 		shell : Shell.Shell;
@@ -53,15 +52,9 @@ TYPE
 		running, dead : BOOLEAN;
 		timer : Kernel.Timer;
 
-		begPos: LONGINT;
-		selectedAll: BOOLEAN;
-		
-		buf: POINTER TO ARRAY OF CHAR;
-
 		PROCEDURE Clear;
 		BEGIN
 			editor.Clear;
-			NewLine(Prompt);
 			Invalidate;
 		END Clear;
 
@@ -73,32 +66,20 @@ TYPE
 		END ExtPointerUp;
 
 		PROCEDURE ExtKeyPressed(ucs : LONGINT; flags : SET; VAR keySym : LONGINT; VAR handled : BOOLEAN);
-		VAR 
-			i, len, n, u: LONGINT;
 		BEGIN
 			handled := FALSE;
 			IF editor.HandleShortcut(ucs, flags, keySym) THEN handled := TRUE; END;
 
-			selectedAll := FALSE;
-
 			IF ~handled & ~(Inputs.Release IN flags) THEN
 				handled := TRUE;
 				IF keySym = 01H THEN (* Ctrl-A *)
-
-					text.AcquireRead;
-					IF editor.editor.tv.cursor.GetPosition() > begPos THEN
-						editor.editor.tv.selection.SetFromTo(begPos,text.GetLength());
-						Texts.SetLastSelection(text,editor.editor.tv.selection.from,editor.editor.tv.selection.to);
-					END;
-					text.ReleaseRead;
-
-					selectedAll := TRUE;
-				(*ELSIF keySym = 03H THEN (* Ctrl-C *)
+					editor.editor.tv.SelectAll
+				ELSIF keySym = 03H THEN (* Ctrl-C *)
 					editor.editor.tv.CopySelection
 				ELSIF keySym = 16H THEN (* Ctrl-V *)
 					CopyFromClipboard;
 	 			ELSIF (keySym = 0FF63H) & (flags * Inputs.Ctrl # {}) THEN  (*Ctrl Insert *)
-	 				editor.editor.tv.CopySelection*)
+	 				editor.editor.tv.CopySelection
 				ELSIF keySym = 0FF56H THEN (* Page Down *)
 					editor.editor.tv.PageDown(flags * Inputs.Shift # {})
 				ELSIF keySym = 0FF55H THEN (* Page Up *)
@@ -107,40 +88,9 @@ TYPE
 					editor.editor.tv.Home(flags * Inputs.Ctrl # {}, flags * Inputs.Shift # {})
 				ELSIF keySym = 0FF57H THEN (* Cursor End *)
 					editor.editor.tv.End(flags * Inputs.Ctrl # {}, flags * Inputs.Shift # {})
-				ELSIF (keySym = Inputs.KsBackSpace) & (flags * Inputs.Ctrl # {}) THEN  (*Ctrl Backspace *)
-					Clear;
-				ELSIF (keySym = Inputs.KsReturn) & (flags*Inputs.Shift = {}) THEN (* ENTER *)
-					text.AcquireRead;
-					len := text.GetLength()-begPos;
-					
-					IF len > 0 THEN
-						IF len >= LEN(buf) THEN NEW(buf,len+(len DIV 4)); END;
-						NEW(r,text);
-						r.SetPosition(begPos);
-					
-						n := 0;
-						FOR i := 0 TO len-1 DO
-							r.ReadCh(u);
-							IF (u >= 32) & (u <= 126) THEN (* take only characters *)
-								buf[n] := CHR(u); INC(n);
-							END; 
-							buf[n] := 0X;
-						END;
-					END;
-					text.ReleaseRead;
-					
-					IF len > 0 THEN
-						out.String(buf^);
-						out.Char(ESC);  out.Char(0DX); out.Update;
-						begPos := begPos + len;						
-					END;
-					editor.editor.KeyPressed(ucs,flags,keySym,handled);
-
-				ELSIF ((keySym = Inputs.KsLeft) OR (keySym = Inputs.KsUp) OR (keySym = Inputs.KsDown)) & (editor.editor.tv.cursor.GetPosition() = begPos) THEN
-					
-				ELSIF (keySym = Inputs.KsBackSpace) & (flags = {}) THEN
-					IF editor.editor.tv.cursor.GetPosition() # begPos THEN
-						handled := FALSE;
+				ELSIF keySym = 0FF1BH THEN (* Esc *)
+					IF ~(Inputs.Release IN flags) THEN
+						out.Char(ESC); out.Char(ESC); out.Update;
 					END;
 				ELSE
 					handled := FALSE;
@@ -148,7 +98,13 @@ TYPE
 			END;
 
 			IF ~handled & (ucs > 0) & (ucs < 256) THEN
-				editor.editor.KeyPressed(ucs,flags,keySym,handled);
+				IF ~(Inputs.Release IN flags) THEN
+					IF ucs > 127 THEN (* Escape non-ascii characters *)
+						out.Char(ESC); out.Char("["); ucs := ucs - 128;
+					END;
+					out.Char(CHR(ucs)); out.Update;
+				END;
+				handled := TRUE;
 			END;
 		END ExtKeyPressed;
 
@@ -169,7 +125,7 @@ TYPE
 			NEW(out, pipeOut.Send, 256);
 			NEW(in, pipeIn.Receive, 256);
 
-			NEW(shell, shellIn,shellOut, shellOut, FALSE, "");
+			NEW(shell, shellIn,shellOut, shellOut, TRUE, Prompt);
 		END InitShell;
 
 		PROCEDURE CopyFromClipboard;
@@ -182,7 +138,6 @@ TYPE
 			END;
 			Texts.clipboard.ReleaseRead;
 			out.String(string^); out.Update;
-			TRACE(string^);
 		END CopyFromClipboard;
 
 		PROCEDURE Finalize;
@@ -203,15 +158,6 @@ TYPE
 			text.Delete(pos - nbrOfCharacters, nbrOfCharacters);
 			text.ReleaseWrite;
 		END DeleteNCharacters;
-		
-		PROCEDURE NewLine(CONST prompt: ARRAY OF CHAR);
-		BEGIN
-			w.Ln; w.String(prompt); w.Update;
-			text.AcquireRead;
-			editor.editor.tv.cursor.SetPosition(text.GetLength());
-			begPos := editor.editor.tv.cursor.GetPosition();
-			text.ReleaseRead;
-		END NewLine;
 
 		PROCEDURE ReceiveCharacters;
 		VAR ch : CHAR; buffer : ARRAY ReceiveBufferSize OF CHAR; backspaces, i, size, len : LONGINT;
@@ -235,7 +181,6 @@ TYPE
 					END;
 				END;
 				w.Update;
-				NewLine(Prompt);
 			END;
 			DeleteNCharacters(backspaces);
 		END ReceiveCharacters;
@@ -257,8 +202,6 @@ TYPE
 			editor.SetText(text);
 			InitShell;
 			SetNameAsString(StrShellComponent);
-			
-			NEW(buf,65536);
 		END Init;
 
 	BEGIN {ACTIVE}
@@ -382,13 +325,7 @@ BEGIN
 	InitStrings;
 END WMInterpreterShell.
 
-WMInterpreterShell.Open ~
-
-SystemTools.Free WMInterpreterShell ~
-SystemTools.Free WMInterpreterShell InterpreterShell ~
-
-FOR i := 0 TO 100 DO
-	CMD "SystemTools.Show ?{i}?"
-END;
-
+WMShell.Open ~
 
+SystemTools.Free WMShell ~
+SystemTools.Free WMShell Shell ~