Skip to content

Commit

Permalink
Issue #1036: DocGen step
Browse files Browse the repository at this point in the history
  • Loading branch information
Brochato committed Dec 18, 2018
1 parent cd32f5f commit b478916
Show file tree
Hide file tree
Showing 12 changed files with 132 additions and 34 deletions.
11 changes: 11 additions & 0 deletions CLI/test/CLITest.cs
Original file line number Diff line number Diff line change
Expand Up @@ -134,6 +134,17 @@ public void TestOutputFormat()
CLITestHelper.Test("outputSignature_1", ReturnCode.Warning);
}


/// <summary>
/// Try parsing with Documentation Generation as output format.
/// Should return success.
/// </summary>
[TestMethod]
public void TestDocGen()
{
CLITestHelper.Test("documentation", ReturnCode.Warning);
}

/// <summary>
/// Test all CLI arguments errors as follow:
///
Expand Down
1 change: 1 addition & 0 deletions CLI/test/ressources/documentation/CLIArguments.txt
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
-1 -i input\DocGen.tcbl -o output\DocGen.json -d output\error.txt -e rdz -f Documentation -s ..\skeletons.xml
68 changes: 68 additions & 0 deletions CLI/test/ressources/documentation/input/DocGen.tcbl
Original file line number Diff line number Diff line change
@@ -0,0 +1,68 @@
 IDENTIFICATION DIVISION.
PROGRAM-ID. DocGen.

DATA DIVISION.
LOCAL-STORAGE SECTION.

*<<<
@ description : inline typedef
@ params:
- none: Type doesn't have any params
@deprec
@Restriction : Do not Use BOOL var
@Params:
- Typedefs: should not have any params
*>>>
01 myType TYPEDEF STRICT PUBLIC pic X(01).

*<<< Vect2D
*>>>
01 Vect2D TYPEDEF STRICT PUBLIC.
02 Coord2d.
03 X PIC 9(4).
03 Y PIC 9(4).


*<<< This type is private
*>>>
01 PrivateType TYPEDEF STRICT pic XXX.


*<<< My program
@ Description description
@deprecated
@ replacedBy MyFonction2
@ rEsTrIcTiOn Do not Use BOOL var
@ need some needs
- description
@ see Thank you for your attention
@ todo
- Add BOOL support
- implement a call counter
*>>>
PROCEDURE DIVISION.

*<<< MyProc info
@ deprec : It is
deprecated
@ need : long need
@ todo:
- todo1
- todo 2
@ params:
- myDate: just a date
- bla: bla < 2
- toto: toto
-blu: will be ignored
*>>>
DECLARE PROCEDURE MyProc PUBLIC
INPUT myDate TYPE Date
bla Pic S9(1)V9(12)
IN-OUT myBool TYPE BOOL
OUTPUT toto TYPE BOOL
bli Pic PPP999PPP.
PROCEDURE DIVISION.
CONTINUE.
END-DECLARE.

END PROGRAM DocGen.
2 changes: 2 additions & 0 deletions CLI/test/ressources/documentation/output_expected/DocGen.json
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
*TypeCobol_Version:0.1(alpha)
{"__type":"DocumentationForProgram:#TypeCobol.Compiler.Nodes","Deprecated":"","Description":"My program description ","Name":"DocGen","Namespace":"DocGen","Needs":["some needs","description"],"ReplacedBy":"MyFonction2 ","Restriction":"Do not Use BOOL var ","See":"Thank you for your attention ","ToDos":["Add BOOL support","implement a call counter"]}{"__type":"DocumentationForType:#TypeCobol.Compiler.Nodes","Deprecated":"","Description":"inline typedef ","Name":"myType","Namespace":"DocGen","Restriction":"Do not Use BOOL var ","Visibility":0,"DocDataType":{"MaxOccurence":1,"Picture":"X(01)"}}{"__type":"DocumentationForType:#TypeCobol.Compiler.Nodes","Description":"Vect2D ","Name":"Vect2D","Namespace":"DocGen","Visibility":0,"Childrens":[{"Childrens":[{"DocDataType":{"MaxOccurence":1,"Picture":"9(4)"},"Name":"X"},{"DocDataType":{"MaxOccurence":1,"Picture":"9(4)"},"Name":"Y"}],"DocDataType":{"MaxOccurence":1},"Name":"Coord2d"}],"DocDataType":{"MaxOccurence":1}}{"__type":"DocumentationForFunction:#TypeCobol.Compiler.Nodes","Deprecated":"It is deprecated ","Description":"MyProc info ","Name":"MyProc","Namespace":"DocGen","Needs":["long need"],"ToDos":["todo1","todo 2"],"Visibility":0,"Parameters":[{"DocDataType":{"MaxOccurence":1,"TypeName":"DATE"},"Info":"just a date","Name":"myDate","PassingType":0},{"DocDataType":{"MaxOccurence":1,"Picture":"S9(1)V9(12)"},"Info":"bla < 2","Name":"bla","PassingType":0},{"DocDataType":{"MaxOccurence":1,"TypeName":"BOOL"},"Name":"myBool","PassingType":2},{"DocDataType":{"MaxOccurence":1,"TypeName":"BOOL"},"Info":"toto","Name":"toto","PassingType":1},{"DocDataType":{"MaxOccurence":1,"Picture":"PPP999PPP"},"Name":"bli","PassingType":1}]}
Original file line number Diff line number Diff line change
@@ -1,51 +1,51 @@
 *TypeCobol_Version:0.1(alpha)
*TypeCobol_Version:0.1(alpha)
IDENTIFICATION DIVISION.
*<<
* Multiline comment
* should be commented
Multiline comment
should be commented
*>>
PROGRAM-ID. Callee.
DATA DIVISION.
working-storage section.
01 MyType1 TYPEDEF STRICT PUBLIC.
05 Var1 pic X.
*<<<
* My public Type 2
My public Type 2
*>>>
01 MyType2 TYPEDEF STRICT PUBLIC.
05 Var2 pic X.
01 MyType5 TYPEDEF STRICT PUBLIC.
05 Var5 pic X.
*<<< My program
* @ Description description
* @deprecated
* @ replacedBy MyFonction2
* @ need some needs
* @ todo
* - make my second type my first type
* - get another type
* @Params:
* - MyType2: my second type
* - MyType3: my third type
* - Mydate: today date
@ Description description
@deprecated
@ replacedBy MyFonction2
@ need some needs
@ todo
- make my second type my first type
- get another type
@Params:
- MyType2: my second type
- MyType3: my third type
- Mydate: today date
*>>>
PROCEDURE DIVISION.
declare procedure check public
input mydate TYPE Date
.
END-DECLARE.
*<<<
* check if the given date is before today
* @params:
* - mydate: tyhe date to test
check if the given date is before today
@params:
- mydate: tyhe date to test
*>>>
declare procedure check2 public
input mydate TYPE Date
.
END-DECLARE.
*<<<
* Same as check2 but with two dates
* @see: check2
Same as check2 but with two dates
@see: check2
*>>>
declare procedure check2 public
input mydate TYPE Date
Expand All @@ -55,8 +55,8 @@
DECLARE PROCEDURE MyPublicProcedure PUBLIC
INPUT mydate TYPE Date
*<<
* Multiline comment
* should be commented
Multiline comment
should be commented
*>>
format PIC X(08)
OUTPUT okay TYPE Bool
Expand Down
7 changes: 4 additions & 3 deletions Codegen/src/GeneratorFactoryManager.cs
Original file line number Diff line number Diff line change
Expand Up @@ -29,10 +29,11 @@ private static GeneratorFactoryManager Singleton
static GeneratorFactoryManager()
{
Singleton = new GeneratorFactoryManager();
Instance.RegisterFactory(OutputFormat.Cobol85.ToString(), (id, document, destination, skeletons, typeCobolVersion) => new DefaultGenerator(document, destination, skeletons, typeCobolVersion));
Instance.RegisterFactory(OutputFormat.Cobol85.ToString(), (id, document, destination, skeletons, typeCobolVersion) => new DefaultGenerator(document, destination, skeletons, typeCobolVersion));
Instance.RegisterFactory(OutputFormat.PublicSignatures.ToString(), (id, document, destination, skeletons, typeCobolVersion) => new SignaturesGenerator(destination, typeCobolVersion));
Instance.RegisterFactory(OutputFormat.ExpandingCopy.ToString(), (id, document, destination, skeletons, typeCobolVersion) => new ExpandingCopyGenerator(document, destination));
Instance.RegisterFactory(OutputFormat.Cobol85Mixed.ToString(), (id, document, destination, skeletons, typeCobolVersion) => new MixedTransformGenerator(document, destination, skeletons, new DefaultGenerator(document, destination, skeletons, typeCobolVersion)));
Instance.RegisterFactory(OutputFormat.ExpandingCopy.ToString(), (id, document, destination, skeletons, typeCobolVersion) => new ExpandingCopyGenerator(document, destination));
Instance.RegisterFactory(OutputFormat.Cobol85Mixed.ToString(), (id, document, destination, skeletons, typeCobolVersion) => new MixedTransformGenerator(document, destination, skeletons, new DefaultGenerator(document, destination, skeletons, typeCobolVersion)));
Instance.RegisterFactory(OutputFormat.Documentation.ToString(), (id, document, destination, skeletons, typeCobolVersion) => new DocumentationGenerator(destination, typeCobolVersion));
}

/// <summary>
Expand Down
4 changes: 2 additions & 2 deletions Codegen/src/Generators/LinearNodeSourceCodeMapper.cs
Original file line number Diff line number Diff line change
Expand Up @@ -1354,11 +1354,11 @@ public void CommentSpecificParts(Node node)
// Formalised Comments of Programs (Formalized Comments of Typedef and Functions is already commented)
if (node is Compiler.Nodes.ProcedureDivision && node.Parent is Compiler.CodeModel.Program)
{
CommentBetweenTokens(node, TokenType.FormalizedCommentsStart, TokenType.FormalizedCommentsStop);
CommentBetweenTokens(node, TokenType.FORMALIZED_COMMENTS_START, TokenType.FORMALIZED_COMMENTS_STOP);
}

// Multilines Comments
CommentBetweenTokens(node, TokenType.MultilinesCommentsStart, TokenType.MultilinesCommentsStop);
CommentBetweenTokens(node, TokenType.MULTILINES_COMMENTS_START, TokenType.MULTILINES_COMMENTS_STOP);

foreach (var child in node.Children)
{
Expand Down
12 changes: 11 additions & 1 deletion Codegen/test/resources/output/TypeCobol/FormalizedComments.tcbl
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,9 @@
88 TC-DocCodeG-FctList-IsLoaded VALUE 'OK'.
01 TC-DocCodeG-PntTab.
05 TC-DocCodeG-PntNbr PIC S9(04) COMP VALUE 1.
*DocCodeG::MyProc
*To call program fd48569eMyProc
*Which is generated code for DocCodeGen.MyProc
*Declared in source file FormalizedComments.tcbl
05 TC-DocCodeG-fd48569e-Idt PIC X(08) VALUE 'fd48569e'.
05 TC-DocCodeG-fd48569e PROCEDURE-POINTER.

Expand Down Expand Up @@ -122,6 +124,10 @@
PROGRAM-ID. fd48569eMyProc.
DATA DIVISION.
LINKAGE SECTION.
*DocCodeGen.MyProc - Params :
* input(myDate: DATE, bla: pic S9(1)V9(12))
* in-out(myBool: BOOL)
* output(toto: BOOL, bli: pic PPP999PPP)
01 myDate.
02 YYYY PIC 9(4).
02 MM PIC 9(2).
Expand All @@ -145,5 +151,9 @@
BY REFERENCE toto-value
BY REFERENCE bli
.
*DocCodeGen.MyProc - Params :
* input(myDate: DATE, bla: pic S9(1)V9(12))
* in-out(myBool: BOOL)
* output(toto: BOOL, bli: pic PPP999PPP)
CONTINUE.
END PROGRAM fd48569eMyProc.
Original file line number Diff line number Diff line change
Expand Up @@ -85,6 +85,8 @@
PROGRAM-ID. acc4f1bfFUN.
DATA DIVISION.
LINKAGE SECTION.
*MultilinesCommentsCodeGen.FUN - Params :
* input(x: myType, y: pic 9(03))
01 x.
02 var0 PIC 9.
02 var1 PIC 9(3).
Expand All @@ -100,6 +102,8 @@
USING BY REFERENCE x
BY REFERENCE y
.
*MultilinesCommentsCodeGen.FUN - Params :
* input(x: myType, y: pic 9(03))
*<<
* Multiline Comment 15 here
*>>
Expand Down
4 changes: 2 additions & 2 deletions TypeCobol.Test/Parser/Programs/Cobol2002/Typedef2PGM.txt
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
--- Diagnostics ---
Line 1[1,24] <37, Warning, General> - Warning: "END PROGRAM" is missing.
Line 17[1,2] <27, Error, Syntax> - Syntax error : extraneous input '01' expecting {separator, numeric literal, symbol, statement starting keyword, keyword} RuleStack=, OffendingSymbol=[1,2:01]<IntegerLiteral>{1}
Line 18[3,4] <27, Error, Syntax> - Syntax error : extraneous input '02' expecting {separator, numeric literal, symbol, statement starting keyword, keyword} RuleStack=, OffendingSymbol=[3,4:02]<IntegerLiteral>{2}
Line 17[1,2] <27, Error, Syntax> - Syntax error : extraneous input '01' expecting {separator, numeric literal, symbol, statement starting keyword, keyword, Formalized Comments elements} RuleStack=, OffendingSymbol=[1,2:01]<IntegerLiteral>{1}
Line 18[3,4] <27, Error, Syntax> - Syntax error : extraneous input '02' expecting {separator, numeric literal, symbol, statement starting keyword, keyword, Formalized Comments elements} RuleStack=, OffendingSymbol=[3,4:02]<IntegerLiteral>{2}

--- Program ---
PROGRAM: TypeCobol common:False initial:False recursive:False
Expand Down
4 changes: 2 additions & 2 deletions TypeCobol/Compiler/Nodes/Procedure.cs
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ public override IEnumerable<TypeCobol.Compiler.Text.ITextLine> Lines
int lastComputedLine = 0;
foreach (var token in CodeElement.ConsumedTokens)
{//JCM: Don't take in account imported token.
if (token.TokenType == TokenType.FormalizedCommentsStart)
if (token.TokenType == TokenType.FORMALIZED_COMMENTS_START)
insideFormalizedComment = true;
if (insideFormalizedComment && lastComputedLine != token.TokensLine.LineIndex)
{
Expand All @@ -63,7 +63,7 @@ public override IEnumerable<TypeCobol.Compiler.Text.ITextLine> Lines
}
sep = " ";
}
if (token.TokenType == TokenType.FormalizedCommentsStop)
if (token.TokenType == TokenType.FORMALIZED_COMMENTS_STOP)
insideFormalizedComment = false;
}
if (!bPeriodSeen)
Expand Down
5 changes: 3 additions & 2 deletions TypeCobol/Tools/Options-Config/TypeCobolConfiguration.cs
Original file line number Diff line number Diff line change
Expand Up @@ -143,7 +143,8 @@ public enum OutputFormat {
Cobol85,
PublicSignatures,
ExpandingCopy,
Cobol85Mixed
Cobol85Mixed,
Documentation
}
public static class TypeCobolOptionSet
{
Expand All @@ -164,7 +165,7 @@ public static OptionSet GetCommonTypeCobolOptions(TypeCobolConfiguration typeCob
{ "dp|dependencies=", "Path to folder containing programs to load and to use for parsing a generating the input program.", v => typeCobolConfig.Dependencies.Add(v) },
{ "t|telemetry", "If set to true telemetry will send automatic email in case of bug and it will provide to TypeCobol Team data on your usage.", v => typeCobolConfig.Telemetry = true },
{ "md|maximumdiagnostics=", "Wait for an int value that will represent the maximum number of diagnostics that TypeCobol have to return.", v => typeCobolConfig.RawMaximumDiagnostics = v},
{ "f|outputFormat=", "Output format (default is Cobol 85). (Cobol85/0, PublicSignature/1, Cobol85Mixed/3).", v =>typeCobolConfig.RawOutputFormat = v},
{ "f|outputFormat=", "Output format (default is Cobol 85). (Cobol85/0, PublicSignature/1, Cobol85Mixed/3, Documentation/4)", v =>typeCobolConfig.RawOutputFormat = v},
{ "ec|expandingcopy=", "Generate a file with all COPY directives expanded in the source code. This option will be executed if the Preprocessor step is enabled.", v => typeCobolConfig.ExpandingCopyFilePath = v },
{ "exc|extractusedcopy=", "Generate a file with all COPIES detected by the parser.", v => typeCobolConfig.ExtractedCopiesFilePath = v },
{ "alr|antlrprogparse", "Use ANTLR to parse a program.", v => typeCobolConfig.UseAntlrProgramParsing = true},
Expand Down

0 comments on commit b478916

Please sign in to comment.