Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
Original file line number Diff line number Diff line change
Expand Up @@ -98,10 +98,6 @@
"category": 0,
"message": "{\"jsonrpc\":\"2.0\",\"method\":\"textDocument/didSave\",\"params\":{\"textDocument\":{\"version\":0,\"uri\":\"file:/C:/Users/LANOYDO/AppData/Local/Temp/1/tcbl/DVZZDLY1103830253336368444.cee\"},\"text\":\" IDENTIFICATION DIVISION.\\r\\n PROGRAM-ID. DVZZBCO0.\\r\\n DATA DIVISION.\\r\\n WORKING-STORAGE SECTION.\\r\\n PROCEDURE DIVISION.\\r\\n call DVZZSTKD::Foo\\r\\n .\\r\\n END PROGRAM DVZZBCO0.\\r\\n\\r\\n IDENTIFICATION DIVISION.\\r\\n PROGRAM-ID. DVZZSTKD.\\r\\n PROCEDURE DIVISION.\\r\\n declare procedure Foo public.\\r\\n procedure division.\\r\\n goback.\\r\\n end-declare.\\r\\n\\r\\n END PROGRAM DVZZSTKD.\"}}"
},
{
"category": 1,
"message": "{\"jsonrpc\":\"2.0\",\"method\":\"textDocument/publishDiagnostics\",\"params\":{\"uri\":\"file:///C:/Users/LANOYDO/AppData/Local/Temp/1/tcbl/DVZZDLY1103830253336368444.cee\",\"diagnostics\":[]}}"
},
{
"category": 1,
"message": "{\"jsonrpc\":\"2.0\",\"method\":\"textDocument/publishDiagnostics\",\"params\":{\"uri\":\"file:///C:/Users/LANOYDO/AppData/Local/Temp/1/tcbl/DVZZDLY1103830253336368444.cee\",\"diagnostics\":[]}}"
Expand Down
63 changes: 40 additions & 23 deletions TypeCobol.LanguageServer/Workspace.cs
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,7 @@ public class Workspace

internal CompilationProject CompilationProject { get; private set; }

private List<FileCompiler> _fileCompilerWaittingForNodePhase;
private List<FileCompiler> _fileCompilerWaitingForNodePhase;
public TypeCobolConfiguration Configuration { get; private set; }
public event EventHandler<DiagnosticEvent> DiagnosticsEvent;
public event EventHandler<EventArgs> DocumentModifiedEvent;
Expand Down Expand Up @@ -162,7 +162,7 @@ public Workspace(string rootDirectoryFullName, string workspaceName, Queue<Messa
MessagesActionsQueue = messagesActionsQueue;
Configuration = new TypeCobolConfiguration();
_openedDocuments = new Dictionary<Uri, DocumentContext>();
_fileCompilerWaittingForNodePhase = new List<FileCompiler>();
_fileCompilerWaitingForNodePhase = new List<FileCompiler>();
_Logger = logger;

this._rootDirectoryFullName = rootDirectoryFullName;
Expand Down Expand Up @@ -234,22 +234,22 @@ private FileCompiler OpenTextDocument(DocumentContext docContext, string sourceT
#else
fileCompiler = new FileCompiler(initialTextDocumentLines, CompilationProject.SourceFileProvider, CompilationProject, CompilationProject.CompilationOptions, _customSymbols, CompilationProject);
#endif
//Set Any Language Server Connection Options.
docContext.FileCompiler = fileCompiler;
docContext.LanguageServerConnection(true);

fileCompiler.CompilationResultsForProgram.UpdateTokensLines();

lock (_lockForOpenedDocuments)
{
if (_openedDocuments.ContainsKey(docContext.Uri))
CloseSourceFile(docContext.Uri); //Close and remove the previous opened file.

_openedDocuments.Add(docContext.Uri, docContext);
fileCompiler.CompilationResultsForProgram.CodeAnalysisCompleted += FinalCompilationStepCompleted;
}

//Set Any Language Server Connection Options.
docContext.FileCompiler = fileCompiler;
docContext.LanguageServerConnection(true);

fileCompiler.CompilationResultsForProgram.SetOwnerThread(Thread.CurrentThread);
fileCompiler.CompilationResultsForProgram.CodeAnalysisCompleted += FinalCompilationStepCompleted;
fileCompiler.CompilationResultsForProgram.UpdateTokensLines();

if (lsrOptions != LsrTestingOptions.LsrSourceDocumentTesting)
{
Expand Down Expand Up @@ -325,14 +325,14 @@ public void UpdateSourceFile(Uri fileUri, TextChangedEvent textChangedEvent)
{
if (!_timerDisabled) //If TimerDisabled is false, create a timer to automatically launch Node phase
{
lock (_fileCompilerWaittingForNodePhase)
lock (_fileCompilerWaitingForNodePhase)
{
if (!_fileCompilerWaittingForNodePhase.Contains(fileCompilerToUpdate))
_fileCompilerWaittingForNodePhase.Add(fileCompilerToUpdate); //Store that this fileCompiler will soon need a Node Phase
if (!_fileCompilerWaitingForNodePhase.Contains(fileCompilerToUpdate))
_fileCompilerWaitingForNodePhase.Add(fileCompilerToUpdate); //Store that this fileCompiler will soon need a Node Phase
}

_semanticUpdaterTimer = new System.Timers.Timer(750);
_semanticUpdaterTimer.Elapsed += (sender, e) => TimerEvent(sender, e, fileCompilerToUpdate);
_semanticUpdaterTimer.Elapsed += (sender, e) => TimerEvent(fileUri);
_semanticUpdaterTimer.Start();
}
}
Expand Down Expand Up @@ -392,23 +392,29 @@ private void ExecutionStepEventHandler(object oFileCompiler, ExecutionStepEventA
/// <param name="sender"></param>
/// <param name="eventArgs"></param>
/// <param name="fileCompiler"></param>
private void TimerEvent(object sender, ElapsedEventArgs eventArgs, FileCompiler fileCompiler)
private void TimerEvent(Uri fileUri)
{
try
{
_semanticUpdaterTimer.Stop();
Action nodeRefreshAction = () => { RefreshSyntaxTree(fileCompiler, SyntaxTreeRefreshLevel.RebuildNodesAndPerformQualityCheck); };
lock (MessagesActionsQueue)
{
MessagesActionsQueue.Enqueue(new MessageActionWrapper(nodeRefreshAction));
MessagesActionsQueue.Enqueue(new MessageActionWrapper(Refresh));
}
}
catch (Exception e)
{
//In case Timer Thread crash
ExceptionTriggered(null, new ThreadExceptionEventArgs(e));
}


void Refresh()
{
if (TryGetOpenedDocumentContext(fileUri, out var docContext))
{
RefreshSyntaxTree(docContext.FileCompiler, SyntaxTreeRefreshLevel.RebuildNodesAndPerformQualityCheck);
}
}
}

/// <summary>
Expand Down Expand Up @@ -446,12 +452,12 @@ public void RefreshSyntaxTree(FileCompiler fileCompiler, SyntaxTreeRefreshLevel
{
if (refreshLevel == SyntaxTreeRefreshLevel.NoRefresh) return; //nothing to do

lock (_fileCompilerWaittingForNodePhase)
lock (_fileCompilerWaitingForNodePhase)
{
var fileCompilerNeedsRefresh = _fileCompilerWaittingForNodePhase.Contains(fileCompiler);
var fileCompilerNeedsRefresh = _fileCompilerWaitingForNodePhase.Contains(fileCompiler);
if (fileCompilerNeedsRefresh)
{
_fileCompilerWaittingForNodePhase.Remove(fileCompiler);
_fileCompilerWaitingForNodePhase.Remove(fileCompiler);
}
else
{
Expand Down Expand Up @@ -495,16 +501,27 @@ void RefreshCodeAnalysisResults()
/// </summary>
public void CloseSourceFile(Uri fileUri)
{
FileCompiler fileCompilerToClose = null;

//Remove from opened documents dictionary
lock (_lockForOpenedDocuments)
{
if (_openedDocuments.ContainsKey(fileUri))
if (_openedDocuments.TryGetValue(fileUri, out var contextToClose))
{
var contextToClose = _openedDocuments[fileUri];
FileCompiler fileCompilerToClose = contextToClose.FileCompiler;
fileCompilerToClose = contextToClose.FileCompiler;
_openedDocuments.Remove(fileUri);
fileCompilerToClose.CompilationResultsForProgram.CodeAnalysisCompleted -= FinalCompilationStepCompleted;
}
}
}

//Remove from pending semantic analysis list
if (fileCompilerToClose != null)
{
lock (_fileCompilerWaitingForNodePhase)
{
_fileCompilerWaitingForNodePhase.Remove(fileCompilerToClose);
}
}
}

/// <summary>
Expand Down
4 changes: 2 additions & 2 deletions TypeCobol.Test/Parser/Preprocessor/PreprocessorUtils.cs
Original file line number Diff line number Diff line change
Expand Up @@ -73,7 +73,7 @@ private static string ProcessTokensDocument(ProcessedTokensDocument processedDoc
StringBuilder sbTokens = new StringBuilder();
ITokensLinesIterator tokens = processedDoc.GetProcessedTokensIterator();
Token token = tokens.NextToken();
if (token != Token.END_OF_FILE)
if (token.TokenType != TokenType.EndOfFile)
{
string documentPath = null;
int lineIndex = -1;
Expand All @@ -91,7 +91,7 @@ private static string ProcessTokensDocument(ProcessedTokensDocument processedDoc
}
sbTokens.AppendLine(token.ToString());
}
while ((token = tokens.NextToken()) != Token.END_OF_FILE);
while ((token = tokens.NextToken()).TokenType != TokenType.EndOfFile);
}

// Errors
Expand Down
4 changes: 2 additions & 2 deletions TypeCobol/Compiler/AntlrUtils/AntlrPerformanceProfiler.cs
Original file line number Diff line number Diff line change
Expand Up @@ -101,8 +101,8 @@ public void BeginParsingFile(TextSourceInfo textSourceInfo, ITokensLinesIterator
if (tokensCountIterator != null)
{
ITokensLine lastLine = null;
Token token = null;
while ((token = tokensCountIterator.NextToken()) != Token.END_OF_FILE)
Token token;
while ((token = tokensCountIterator.NextToken()).TokenType != TokenType.EndOfFile)
{
CurrentFileInfo.TokensCount++;
if (token.TokensLine != lastLine)
Expand Down
4 changes: 2 additions & 2 deletions TypeCobol/Compiler/AntlrUtils/TokensLinesTokenStream.cs
Original file line number Diff line number Diff line change
Expand Up @@ -61,15 +61,15 @@ public void SeekToToken(IToken searchedToken)
}

/// <summary>
/// Start monitoring if the token stream reached a specific token which marks the end of an instersting section
/// Start monitoring if the token stream reached a specific token which marks the end of an interesting section
/// </summary>
public void StartLookingForStopToken(Token stopToken)
{
ResetStopTokenLookup();
if (stopToken != null)
{
StopToken = stopToken;
stopTokenReplacedByEOF = new ReplacedToken(Token.END_OF_FILE, stopToken);
stopTokenReplacedByEOF = new ReplacedToken(Token.EndOfFile(), stopToken);
StreamReachedStopToken = false;
}
}
Expand Down
30 changes: 8 additions & 22 deletions TypeCobol/Compiler/CupCommon/CobolWordsTokenizer.cs
Original file line number Diff line number Diff line change
Expand Up @@ -233,7 +233,7 @@ public void LeaveAnyTokenMode(bool bAllMode = false)
public void ConsumeNextTokenOnTheSameLine(TokenType nextTokenType)
{
Token currentToken = base.CurrentToken;
if (currentToken == Token.END_OF_FILE)
if (currentToken != null && currentToken.TokenType == TokenType.EndOfFile)
return;//Ignore if end of file
Token nextToken = base.NextToken();
if (nextToken != null && currentToken != null &&
Expand All @@ -258,21 +258,6 @@ public void ConsumeNextTokenOnTheSameLineAndStop(TokenType nextTokenType)
EnterStopScanningMode();
}

/// <summary>
/// Enter in the Stop Scanning Mode if the current is not of the given type
/// </summary>
/// <param name="tokenType">The Token type to check</param>
public void EnterStopScanningModeIfNotToken(TokenType tokenType)
{
Token currentToken = base.CurrentToken;
if (currentToken == null)
return;
if (currentToken == Token.END_OF_FILE)
return;//Ignore if end of file
if (currentToken.TokenType != tokenType)
EnterStopScanningMode();
}

/// <summary>
/// Enter in the Stop Scanning Mode if the next is not of the given type
/// </summary>
Expand All @@ -282,7 +267,7 @@ public void EnterStopScanningModeIfNextNotToken(TokenType nextTokenType)
Token currentToken = base.CurrentToken;
if (currentToken == null)
return;
if (currentToken == Token.END_OF_FILE)
if (currentToken.TokenType == TokenType.EndOfFile)
return;//Ignore if end of file
Token nextToken = base.NextToken();
base.PreviousToken();
Expand Down Expand Up @@ -326,11 +311,12 @@ private bool BasicAnyTokenMode(Token token, Symbol symbol)
/// </summary>
/// <param name="expected">The expected next token</param>
/// <param name="resulting">The resulting token if matching</param>
/// <param name="defaultToken">The defualt token if no matching</param>
/// <param name="defaultToken">The default token if no matching</param>
/// <returns></returns>
private int TryMatchNextToken(TokenType expected, int resulting, int defaultToken)
{
if (base.CurrentToken == Token.END_OF_FILE)
var currentToken = base.CurrentToken;
if (currentToken != null && currentToken.TokenType == TokenType.EndOfFile)
return defaultToken;
Token nextToken = base.NextToken();
if (nextToken != null)
Expand All @@ -350,11 +336,11 @@ private int TryMatchNextToken(TokenType expected, int resulting, int defaultToke
/// </summary>
/// <param name="expected">The expected next token</param>
/// <param name="resulting">The resulting token if matching</param>
/// <param name="defaultToken">The defualt token if no matching</param>
/// <param name="defaultToken">The default token if no matching</param>
/// <returns></returns>
private int TryMatchPrevToken(TokenType expected, int resulting, int defaultToken)
{
if (base.CurrentToken == Token.END_OF_FILE)
if (base.CurrentToken == null)
return defaultToken;
Token prevToken = base.PreviousToken();
if (prevToken != null)
Expand Down Expand Up @@ -436,7 +422,7 @@ public IEnumerator<Symbol> GetEnumerator()
FirstToken = null;
LastToken = null;
Token token = null;
while ((token = base.NextToken()) != Token.END_OF_FILE)
while ((token = base.NextToken()).TokenType != TokenType.EndOfFile)
{
if (FirstToken == null)
{
Expand Down
2 changes: 1 addition & 1 deletion TypeCobol/Compiler/Parser/CodeElementsLinesTokenSource.cs
Original file line number Diff line number Diff line change
Expand Up @@ -103,7 +103,7 @@ public IToken NextToken()
}
}

return Token.END_OF_FILE;
return Token.EndOfFile();
}

public string SourceName
Expand Down
14 changes: 8 additions & 6 deletions TypeCobol/Compiler/Preprocessor/CopyTokensLinesIterator.cs
Original file line number Diff line number Diff line change
Expand Up @@ -254,15 +254,16 @@ public Token NextToken()
// If the document is empty or after end of file, immediately return EndOfFile
if (currentLine == null)
{
currentPosition.CurrentToken = Token.END_OF_FILE;
return Token.END_OF_FILE;
var eof = Token.EndOfFile();
currentPosition.CurrentToken = eof;
return eof;
}

// If the iterator is positioned in an imported document, return the next imported token
if(currentPosition.ImportedDocumentIterator != null)
{
Token nextImportedToken = currentPosition.ImportedDocumentIterator.NextToken();
if(nextImportedToken == Token.END_OF_FILE)
if(nextImportedToken.TokenType == TokenType.EndOfFile)
{
currentPosition.ImportedDocumentIterator = null;
currentPosition.ImportedDocumentIteratorPosition = null;
Expand Down Expand Up @@ -297,8 +298,9 @@ public Token NextToken()
{
// return EndOfFile
currentLine = null;
currentPosition.CurrentToken = Token.END_OF_FILE;
return Token.END_OF_FILE;
var eof = Token.EndOfFile();
currentPosition.CurrentToken = eof;
return eof;
}
}
// Check if the next token found matches the filter criteria or is a COPY compiler directive or is a REPLACE directive
Expand All @@ -322,7 +324,7 @@ public Token NextToken()

// No suitable next token found in the imported document
// -> get next token in the main document
if (nextTokenCandidate == Token.END_OF_FILE)
if (nextTokenCandidate.TokenType == TokenType.EndOfFile)
{
return NextToken();
}
Expand Down
2 changes: 1 addition & 1 deletion TypeCobol/Compiler/Scanner/ITokensLinesIterator.cs
Original file line number Diff line number Diff line change
Expand Up @@ -51,7 +51,7 @@ public interface ITokensLinesIterator
/// <summary>
/// Get next token or EndOfFile
/// </summary>
Token NextToken();
Token NextToken();

/// <summary>
/// Get null (before the first call to NextToken()), current token, or EndOfFile
Expand Down
10 changes: 8 additions & 2 deletions TypeCobol/Compiler/Scanner/Token.cs
Original file line number Diff line number Diff line change
Expand Up @@ -413,8 +413,14 @@ public int TokenIndex
get { return -1; }
}

// Common token for End of file
public static Token END_OF_FILE = new Token(TokenType.EndOfFile, 0, -1, TypeCobol.Compiler.Scanner.TokensLine.CreateVirtualLineForInsertedToken(-1, String.Empty));
/// <summary>
/// Creates a new instance of special end-of-file Token.
/// </summary>
/// <returns>New Token instance with EndOfFile TokenType</returns>
public static Token EndOfFile()
{
return new Token(TokenType.EndOfFile, 0, -1, Compiler.Scanner.TokensLine.CreateVirtualLineForInsertedToken(-1, string.Empty));
}

// --- Token comparison for REPLACE directive ---

Expand Down
4 changes: 2 additions & 2 deletions TypeCobol/Compiler/Scanner/TokensLinesIterator.cs
Original file line number Diff line number Diff line change
Expand Up @@ -199,7 +199,7 @@ public Token NextToken(bool applyChannelFilter)
// If document is empty, immediately return EndOfFile
if (currentLine == null)
{
return Token.END_OF_FILE;
return Token.EndOfFile();
}

// While we can find a next token
Expand All @@ -224,7 +224,7 @@ public Token NextToken(bool applyChannelFilter)
{
// return EndOfFile
currentLine = null;
return Token.END_OF_FILE;
return Token.EndOfFile();
}
}
// Check if the next token found matches the filter criteria
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -296,7 +296,7 @@ public static void GenerateStatisticsForPrograms(CompilationProject project, IEn
// Iterate over tokens AFTER preprocessing
ITokensLinesIterator processedTokensIterator = compilationResult.ProcessedTokensDocumentSnapshot.GetProcessedTokensIterator();
Token processedToken = null;
while ((processedToken = processedTokensIterator.NextToken()) != Token.END_OF_FILE)
while ((processedToken = processedTokensIterator.NextToken()).TokenType != TokenType.EndOfFile)
{
tokensCounter.OnElement((int)processedToken.TokenType);
ReplacedToken replacedToken = processedToken as ReplacedToken;
Expand Down