Eagle Legacy Modernization, LLC

COBOL Grammar

Main programs: COBOL_Partial_Fixed_Format COBOL_Program_Fixed_Format COBOL_Program_Free_Format

COBOL Fixed syntax:

COBOL Fixed syntax:

COBOL Free syntax:

 Count  Terminals:
4 COBOL_Class_Definition: An identifier
149,342 COBOL_Comment: * comment
14,630 COBOL_CommentToEndOfLine: comment to end of line
193,862 COBOL_Data_Definition: An identifier
41,499 COBOL_FileName: A filename.
934 COBOL_File_Definition: An identifier
9,803 COBOL_HexNumber: A hex number
  COBOL_Identifier: An identifier
551,279 COBOL_Identifier_Reference: An identifier
24 COBOL_Index_Definition: An identifier
263,882 COBOL_Level: COBOL level number, such as 01, 05 or 77.
162,568 COBOL_Literal: quotes:'" escape:none doubled:yes multiline:no
304,822 COBOL_Modifiable_Identifier: An identifier
342,503 COBOL_Number: exponent_chars:none suffix_chars:none trailing_period:no ignore_char:none
56,229 COBOL_Paragraph_Definition: An identifier
189,375 COBOL_Picture: A COBOL PICTURE, such 99V99 or X(10)
956 COBOL_Program_Definition: An identifier
42 COBOL_ReportLine_Definition: An identifier
11 COBOL_Report_Definition: An identifier
8,343 COBOL_Section_Definition: An identifier
 Count  Statistics(*) Tokens:
28,851 2.11(0%) all all COBOL_Copy_Directive: [COBOL_Comment]* COBOL_CopyStatement '.'
221,305 5.65(1%) all 100% 1.39(86%) all 0% 3.72(23%) COBOL_DataDeclaration: [COBOL_Comment]* COBOL_Level [COBOL_DataFieldName] [COBOL_DataClause]* '.' [COBOL_DataComment] [COBOL_CopyOrDataDeclaration]*
265,065 (0% | 0% | 0% | none | 3% | 66% | 5% | 0% | 0% | 0% | 0% | none | 16% | 10% | 0%) |   COBOL_DataClause: (COBOL_Type | COBOL_BlankWhenZero | COBOL_Justified | COBOL_ObjectReference | COBOL_OccursClause | COBOL_PictureClause | COBOL_RedefinesClause | COBOL_RenamesClause | COBOL_Sign | COBOL_ThruClause | COBOL_TypeLiteral | COBOL_Typedef | COBOL_Usage | COBOL_ValueClause | COBOL_ValueIsGlobal)
813 all all |   COBOL_DataComment: '*' COBOL_CommentToEndOfLine
221,304 (15% | 85%) |   COBOL_DataFieldName: ("FILLER" | COBOL_Data_Definition)
2 all all |   COBOL_Justified: "JUSTIFIED" "RIGHT"
8,461 all all 0% all 0% 0% 0% |   COBOL_OccursClause: "OCCURS" COBOL_Expression [COBOL_OccursTo] ["TIMES"] [COBOL_Depending] [COBOL_OccursKey] [COBOL_IndexedBy]
2 all all all |   |   COBOL_Depending: "DEPENDING" "ON" COBOL_Identifier_Reference
24 all all all |   |   COBOL_IndexedBy: "INDEXED" "BY" COBOL_Index_Definition
4 all all all all |   |   COBOL_OccursKey: "ASCENDING" "KEY" ["IS"] COBOL_Identifier_Reference
2 all all |   |   COBOL_OccursTo: "TO" COBOL_Expression
1 (none | all) |   COBOL_TypeLiteral: ("TYPE" | COBOL_Literal)
1 all all |   COBOL_ValueIsGlobal: "IS" "GLOBAL"
952 100% 4.78 COBOL_DataDivision: [COBOL_DataDivisionHeader] COBOL_DataSection*
9,463 (68% | 26% | 7%) |   COBOL_Copy_or_FileDescriptor: (COBOL_Copy_Directive | COBOL_Comment | COBOL_FileDescriptor)
948 all all all |   COBOL_DataDivisionHeader: "DATA" "DIVISION" '.'
4,555 (27% | 19% | 21% | 0% | 17% | 16% | 0%) |   COBOL_DataSection: (COBOL_Comment | COBOL_FileSection | COBOL_WorkingStorage | COBOL_LocalStorageSection | COBOL_ScreenSection | COBOL_LinkageSection | COBOL_ReportSection)
864 all all all 10.95 |   COBOL_FileSection: "FILE" "SECTION" '.' COBOL_Copy_or_FileDescriptor*
734 all all all 1.11 |   COBOL_LinkageSection: "LINKAGE" "SECTION" '.' COBOL_CopyOrDataDeclaration*
2 all all all none |   COBOL_LocalStorageSection: "LOCAL-STORAGE" "SECTION" '.' [COBOL_CopyOrDataDeclaration]*
11 all all all 1.00 |   COBOL_ReportSection: "REPORT" "SECTION" '.' COBOL_ReportEntry*
1,214 all all COBOL_Directive: '$' COBOL_WhichDirective
1,214 (none | none | all | none) |   COBOL_WhichDirective: (COBOL_IfDefinedDirective | COBOL_IfExprDirective | COBOL_SetDirective | "END")
    |   |   COBOL_IfDefinedDirective: "IF" COBOL_Identifier "NOT" "DEFINED"
    |   |   COBOL_IfExprDirective: "IF" COBOL_Expression
1,214 all 1.01 |   |   COBOL_SetDirective: "SET" COBOL_SetWhat*
    |   |   |   COBOL_SetParensNumber: ("INTCODE") '(' COBOL_Number ')'
2 all all all all all |   |   |   COBOL_SetParensPlus: ("OOCTRL"|"PREPROCESS"|"REMOVE") '(' ['+'] ("CONTROL"|"P"|"WINDOW1") ')'
1,223 all 81% |   |   |   COBOL_SetString: ("ANS85"|"CASE"|"CONSTANT"|"DATALIT"|"DEFAULTBYTE"|"DIALECT"|"ISO2002"|"KEYCOMPRESS"|"LINKCOUNT"|"MF"|"MFOO"|"NESTCALL"|"NOALTER"|"NOKEYCOMPRESS"|"NOOSVS"|"NOQUAL"|"NOVSC2"|"QUAL"|"SOURCEFORMAT") [COBOL_Literal]
1,225 (100% | 0% | none) |   |   |   COBOL_SetWhat: (COBOL_SetString | COBOL_SetParensPlus | COBOL_SetParensNumber)
879 all all all 1.00(0%) 1.89(99%) COBOL_EnvironmentDivision: "ENVIRONMENT" "DIVISION" '.' [COBOL_Comment]* [COBOL_EnvironmentEntry]*
2 all all 2.00 all |   COBOL_ClassControl: "CLASS-CONTROL" '.' COBOL_ClassControlIs* '.'
4 all all all all |   |   COBOL_ClassControlIs: COBOL_Class_Definition "IS" "CLASS" COBOL_Literal
779 all all all none 2.00(1%) 99% 1.00(0%) |   COBOL_ConfigurationSection: "CONFIGURATION" "SECTION" '.' [COBOL_Comment]* [COBOL_Computer]* [COBOL_SpecialNames] [COBOL_Comment]*
10 all all all all |   |   COBOL_Computer: ("SOURCE-COMPUTER"|"OBJECT-COMPUTER") '.' COBOL_Identifier_Reference '.'
1,647 (0% | 47% | 53% | none | 0%) |   COBOL_EnvironmentEntry: (COBOL_ClassControl | COBOL_ConfigurationSection | COBOL_InputOutputSection | COBOL_SpecialNames | COBOL_FileControl)
3 all all all |   COBOL_IOControl: "I-O-CONTROL" '.' COBOL_IOControlSame
3 all all all all all all all |   |   COBOL_IOControlSame: "SAME" "RECORD" "AREA" "FOR" "NETWORK" "SHARED" '.'
871 (99% | 0% | 1%) |   COBOL_IOSectionEntry: (COBOL_FileControl | COBOL_IOControl | COBOL_IOControlSelect)
865 all all all 1.00(0%) 1.01(100%) |   COBOL_InputOutputSection: "INPUT-OUTPUT" "SECTION" '.' [COBOL_Comment]* [COBOL_IOSectionEntry]*
804,968 (15% | 21% | 0% | 0% | 0% | 0% | 6% | 2% | 0% | none | 0% | none | 1% | 40% | 0% | 0% | 0% | 1% | 1% | 0% | 11% | 0% | 1% | 0%) COBOL_Expression: (COBOL_Literal | COBOL_Number | COBOL_HexNumber | COBOL_LengthExpression | COBOL_AddressExpression | COBOL_LinageCounterExpression | COBOL_BuiltIn | COBOL_ParenthesizedExpression | COBOL_LengthFunction | COBOL_TrimFunction | COBOL_ExpressionFunction | COBOL_SignedExpression | COBOL_LogicalNotCondition | COBOL_VariableExpression | COBOL_ThroughExpression | COBOL_ConcatenateExpression | COBOL_ExponentExpression | COBOL_MultiplicativeExpression | COBOL_AdditiveExpression | COBOL_ClassCondition | COBOL_RelationCondition | COBOL_LogicalAndCondition | COBOL_LogicalOrCondition | COBOL_IsType)
861 all all 8.99(100%) COBOL_FileControl: "FILE-CONTROL" '.' [COBOL_Copy_or_FileSelect]*
7,707 (82% | 5% | 2% | 11%) |   COBOL_Copy_or_FileSelect: (COBOL_Copy_Directive | COBOL_Comment | COBOL_Directive | COBOL_FileSelect)
934 all all 18% 1% 0% 47% 30% 7% all 3.11(99%) COBOL_FileDescriptor: ("FD"|"SD") COBOL_File_Definition [COBOL_FD_ReportExternal] [COBOL_FD_RecordContains] [COBOL_FD_RecordIsVarying] [COBOL_FD_LabelRecordStandard] [COBOL_FD_LabelRecordOmitted] [COBOL_FD_RecordingMode] '.' [COBOL_CopyOrDataDeclaration]*
277 all all all 69% |   COBOL_FD_LabelRecordOmitted: "LABEL" "RECORD" "OMITTED" [COBOL_FD_Linage]
190 all all all |   |   COBOL_FD_Linage: "LINAGE" ["IS"] COBOL_Expression
440 all all all all 96% |   COBOL_FD_LabelRecordStandard: "LABEL" ("RECORD"|"RECORDS") [("IS"|"ARE")] "STANDARD" [COBOL_FD_LabelRecordValue]
422 all all all all all |   |   COBOL_FD_LabelRecordValue: "VALUE" "OF" "FILE-ID" ["IS"] COBOL_FileId
422 (91% | 9%) |   |   |   COBOL_FileId: (COBOL_Identifier_Reference | COBOL_Literal)
6 all all all all |   COBOL_FD_RecordContains: "RECORD" "CONTAINS" COBOL_Number "CHARACTERS"
1 all all all all all all all all |   COBOL_FD_RecordIsVarying: "RECORD" "IS" "VARYING" "IN" "SIZE" "DEPENDING" "ON" COBOL_Identifier_Reference
64 all all all all |   COBOL_FD_RecordingMode: "RECORDING" "MODE" "IS" "VARIABLE"
164 (93% | 7%) |   COBOL_FD_ReportExternal: (COBOL_FD_IsExternal | COBOL_FD_ReportIs)
153 all all none |   |   COBOL_FD_IsExternal: "IS" "EXTERNAL" [COBOL_Identifier_Reference]
11 all all all all |   |   COBOL_FD_ReportIs: "REPORT" "IS" ["EXTERNAL"] [COBOL_Identifier_Reference]
1,010 all all all all all all all 3.68(96%) all COBOL_FileSelect: "SELECT" ["NOT"] ["OPTIONAL"] COBOL_Identifier_Reference "ASSIGN" ["TO"] COBOL_AssignTo [COBOL_SelectClause]* '.'
1,010 (20% | 50% | 30%) |   COBOL_AssignTo: (COBOL_Literal | "DISK" | COBOL_Identifier_Reference)
3,574 (17% | 15% | 14% | 12% | 27% | 9% | 2% | 3%) |   COBOL_SelectClause: (COBOL_SelectAccess | COBOL_SelectAlternate | COBOL_SelectFile | COBOL_SelectLock | COBOL_SelectOrganization | COBOL_SelectRecord | COBOL_SelectRelative | COBOL_Comment)
625 all all all all |   |   COBOL_SelectAccess: "ACCESS" ["MODE"] ["IS"] ("SEQUENTIAL"|"DYNAMIC"|"RANDOM")
527 all all all all all 50% all all |   |   COBOL_SelectAlternate: "ALTERNATE" ["RECORD"] ["KEY"] ["IS"] COBOL_Identifier_Reference [COBOL_SelectAlternates] ["WITH"] ["DUPLICATES"]
263 all 2.30 |   |   |   COBOL_SelectAlternates: '=' COBOL_Identifier_Reference*
505 all all all all |   |   COBOL_SelectFile: ["FILE"] "STATUS" ["IS"] COBOL_Identifier_Reference
428 all all all 27% |   |   COBOL_SelectLock: ("LOCK"|"LOCKING") ["IS"] ("EXCLUSIVE"|"AUTOMATIC"|"MANUAL") [COBOL_SelectLockWith]
117 all all all all all |   |   |   COBOL_SelectLockWith: "WITH" "LOCK" "ON" "MULTIPLE" "RECORDS"
971 all all all all |   |   COBOL_SelectOrganization: "ORGANIZATION" ["IS"] ["LINE"] ("INDEXED"|"SEQUENTIAL"|"RELATIVE")
332 all all all all 2% |   |   COBOL_SelectRecord: "RECORD" ["KEY"] ["IS"] COBOL_Identifier_Reference [COBOL_SelectRecordEquals]
7 all 2.86 |   |   |   COBOL_SelectRecordEquals: '=' COBOL_Identifier_Reference*
89 all all all all |   |   COBOL_SelectRelative: "RELATIVE" ["KEY"] ["IS"] COBOL_Identifier_Reference
8 all all all all all 4.50 all COBOL_IOControlSelect: "SELECT" COBOL_Identifier_Reference "ASSIGN" "TO" COBOL_Literal COBOL_IOSelectClause* '.'
36 (17% | 17% | 22% | 44%) |   COBOL_IOSelectClause: (COBOL_IOSelectAccess | COBOL_IOSelectFile | COBOL_IOSelectOrganization | COBOL_IOSelectRecord)
6 all all all all |   |   COBOL_IOSelectAccess: "ACCESS" "MODE" "IS" "DYNAMIC"
6 all all all all |   |   COBOL_IOSelectFile: "FILE" "STATUS" "IS" COBOL_Identifier_Reference
8 all all all all all |   |   COBOL_IOSelectOrganization: "ORGANIZATION" "IS" ["INDEXED"] ["LINE"] ["SEQUENTIAL"]
16 all all all all all all all |   |   COBOL_IOSelectRecord: ["ALTERNATE"] "RECORD" "KEY" "IS" COBOL_Identifier_Reference ["WITH"] ["DUPLICATES"]
957 all 1% 2.00(0%) 2.86(98%) none COBOL_IdentificationDivision: COBOL_IdentificationHeader [COBOL_IdentificationIsInitial] [COBOL_Comment]* [COBOL_IdentificationEntry]* [COBOL_Comment]*
2,695 (none | 0% | none | 10% | 90%) |   COBOL_IdentificationEntry: (COBOL_IdentificationClassControl | COBOL_IdentificationRepository | COBOL_SpecialNames | COBOL_Comment | COBOL_IdentificationSimple)
    |   |   COBOL_IdentificationClassControl: "CLASS-CONTROL" '.' COBOL_IdentificationClassEntry*
    |   |   |   COBOL_IdentificationClassEntry: COBOL_Identifier_Reference "IS" "CLASS" COBOL_Literal '.'
1 all all 1.00 |   |   COBOL_IdentificationRepository: "REPOSITORY" '.' COBOL_RepositoryEntry*
1 all all all all all |   |   |   COBOL_RepositoryEntry: ("CLASS"|"ENUM") COBOL_Identifier_Reference "AS" COBOL_Literal ['.']
957 (0% | 100%) |   COBOL_IdentificationHeader: (COBOL_ProgramId | COBOL_IdentificationPresent)
9 all all all all |   COBOL_IdentificationIsInitial: "IS" ("COMMON"|"INITIAL") ["PROGRAM"] ['.']
956 all all all 1.00(0%) 100% |   COBOL_IdentificationPresent: ("IDENTIFICATION"|"ID") "DIVISION" '.' [COBOL_Comment]* [COBOL_ProgramId]
2,425 all all 5.70 |   COBOL_IdentificationSimple: ("AUTHOR"|"INSTALLATION"|"DATE-WRITTEN"|"DATE-COMPILED"|"SECURITY") ['.'] COBOL_CommentToEndOfLine*
956 all all all 0% 99% |   COBOL_ProgramId: "PROGRAM-ID" ['.'] COBOL_Program_Definition [COBOL_Program_Subname] ['.']
1 all all |   COBOL_Program_Subname: '.' "CBL"
521 all all all COBOL_Overflow: ["ON"] "OVERFLOW" COBOL_Statement
57,682 1.01(97%) 8.24 COBOL_Paragraph: [COBOL_ParagraphHeader]* COBOL_SentenceOrComment*
56,229 all all |   COBOL_ParagraphHeader: COBOL_Paragraph_Definition '.'
475,368 (0% | 21% | 78% | 1%) |   COBOL_SentenceOrComment: (COBOL_DataInParagraph | COBOL_Comment | COBOL_Sentence | COBOL_ScreenDeclaration)
595 2.17 |   |   COBOL_DataInParagraph: COBOL_CopyOrDataDeclaration*
1,464 6.51 COBOL_Partial_Fixed_Format: COBOL_PartialWhat*
9,533 (2% | 62% | 29% | 1% | none | none | 3% | 2%) |   COBOL_PartialWhat: (COBOL_Directive | COBOL_Comment | COBOL_Paragraph | COBOL_Section | COBOL_ScreenDeclaration | COBOL_DataDeclaration | COBOL_FileDescriptor | COBOL_FileSelect)
25,764 (0% | 5% | 12% | 59% | 22% | 0%) COBOL_Picture_Value: (COBOL_PictureNext | COBOL_Picture_Value_HexNumber | COBOL_Picture_Value_Keyword | COBOL_Picture_Value_Literal | COBOL_Picture_Value_Number | COBOL_Expression)
84 all 50% |   COBOL_PictureNext: "NEXT" [COBOL_PictureNextMinus]
42 all all |   |   COBOL_PictureNextMinus: '-' COBOL_Identifier_Reference
1,398 0% all all |   COBOL_Picture_Value_HexNumber: [','] ['&'] COBOL_HexNumber
3,197 none all |   COBOL_Picture_Value_Keyword: [','] ("ZERO"|"ZEROS"|"SPACE"|"SPACES"|"LOW-VALUE"|"LOW-VALUES"|"HIGH-VALUE"|"HIGH-VALUES")
15,320 0% all 0% |   COBOL_Picture_Value_Literal: [','] COBOL_Literal [COBOL_ThruLiteral]
27 all all |   |   COBOL_ThruLiteral: "THRU" COBOL_Literal
5,723 0% all |   COBOL_Picture_Value_Number: [','] COBOL_Number
958 none all all 77% 0% all all 0% 8.76 0% COBOL_ProcedureDivision: [COBOL_Comment]* "PROCEDURE" "DIVISION" [COBOL_ProcedureUsing] [COBOL_ProcedureChaining] ["WINAPI"] '.' [COBOL_Declaratives] COBOL_Section* [COBOL_ParagraphHeader]
3 all all all all all all |   COBOL_Declaratives: "DECLARATIVES" '.' COBOL_Section "END" "DECLARATIVES" '.'
2 all all 2.00(all) |   COBOL_ProcedureChaining: "CHAINING" COBOL_Identifier_Reference [COBOL_ProcedureChainingWhat]*
4 none all |   |   COBOL_ProcedureChainingWhat: [','] COBOL_Identifier_Reference
734 all none all 3.21(99%) |   COBOL_ProcedureUsing: "USING" [COBOL_ProcedureUsingBy] COBOL_Identifier_Reference [COBOL_ProcedureUsingWhat]*
    |   |   COBOL_ProcedureUsingBy: "BY" ("CONTENT"|"REFERENCE"|"VALUE")
2,331 1% none all |   |   COBOL_ProcedureUsingWhat: [','] [COBOL_ProcedureUsingBy] COBOL_Identifier_Reference
14 all all all all |   COBOL_EndProgram: "END" "PROGRAM" COBOL_Identifier_Reference '.'
781 18.67(6%) 1.00(93%) 20.79(92%) 0% 100% 100% none all all none none COBOL_Program_Fixed_Format: [COBOL_Comment]* [COBOL_Directive]* [COBOL_Comment]* [COBOL_SpecialNames] [COBOL_IdentificationDivision] [COBOL_EnvironmentDivision] [COBOL_Comment]* [COBOL_DataDivision] COBOL_ProcedureDivision [COBOL_Program_Free_Format]* [COBOL_EndProgram]
177 none 1.02(35%) none none all 56% none 97% all 1.50(3%) 8% COBOL_Program_Free_Format: [COBOL_Comment]* [COBOL_Directive]* [COBOL_Comment]* [COBOL_SpecialNames] [COBOL_IdentificationDivision] [COBOL_EnvironmentDivision] [COBOL_Comment]* [COBOL_DataDivision] COBOL_ProcedureDivision [COBOL_Program_Free_Format]* [COBOL_EndProgram]
91,294 (0% | 0% | 0% | 100%) COBOL_RelationalOperator: (COBOL_Equal | COBOL_Greater | COBOL_Less | ("<="|"<"|"="|">="|">"|"<>"))
49 all all |   COBOL_Equal: ("EQUAL"|"EQUALS") ["TO"]
22 all all none |   COBOL_Greater: "GREATER" ["THAN"] [COBOL_GreaterOrEqual]
    |   |   COBOL_GreaterOrEqual: "OR" "EQUAL" ["TO"]
6 all all none |   COBOL_Less: "LESS" ["THAN"] [COBOL_LessOrEqual]
    |   |   COBOL_LessOrEqual: "OR" "EQUAL" ["TO"]
54 (37% | 20% | 13% | 20% | 4% | 6%) COBOL_ReportDataLineType: (COBOL_ReportDataLineTypeControlFooting | COBOL_ReportDataLineTypeDetail | COBOL_ReportDataLineTypePageFooting | COBOL_ReportDataLineTypePageHeading | COBOL_ReportDataLineTypeReportFooting | COBOL_ReportDataLineTypeReportHeading)
20 all all all 70% |   COBOL_ReportDataLineTypeControlFooting: "CONTROL" "FOOTING" ["FINAL"] [COBOL_Identifier_Reference]
11 all |   COBOL_ReportDataLineTypeDetail: "DETAIL"
7 all all |   COBOL_ReportDataLineTypePageFooting: "PAGE" "FOOTING"
11 all all |   COBOL_ReportDataLineTypePageHeading: "PAGE" "HEADING"
2 all all |   COBOL_ReportDataLineTypeReportFooting: "REPORT" "FOOTING"
3 all all |   COBOL_ReportDataLineTypeReportHeading: "REPORT" "HEADING"
63 (16% | 17% | 17% | 14% | 17% | 17%) COBOL_ReportDescriptionEntry: (COBOL_ReportDescriptionControls | COBOL_ReportDescriptionFirstDetail | COBOL_ReportDescriptionFooting | COBOL_ReportDescriptionHeading | COBOL_ReportDescriptionLastDetail | COBOL_ReportDescriptionPageLimit)
10 all all all 1.60 |   COBOL_ReportDescriptionControls: "CONTROLS" "ARE" ["FINAL"] COBOL_Identifier_Reference*
11 all all all |   COBOL_ReportDescriptionFirstDetail: "FIRST" "DETAIL" COBOL_Number
11 all all |   COBOL_ReportDescriptionFooting: "FOOTING" COBOL_Number
9 all all |   COBOL_ReportDescriptionHeading: "HEADING" COBOL_Number
11 all all all |   COBOL_ReportDescriptionLastDetail: "LAST" "DETAIL" COBOL_Number
11 all all all all |   COBOL_ReportDescriptionPageLimit: "PAGE" "LIMIT" "IS" COBOL_Number
11 all 4.91 COBOL_ReportEntry: COBOL_ReportDescription COBOL_ReportDataLine*
54 all 54% all all all 30% all 1.85 |   COBOL_ReportDataLine: COBOL_Level [COBOL_ReportLine_Definition] "TYPE" "IS" COBOL_ReportDataLineType [COBOL_ReportNextGroup] '.' COBOL_ReportLine*
11 all all 5.73 all |   COBOL_ReportDescription: "RD" COBOL_Report_Definition COBOL_ReportDescriptionEntry* '.'
16 all all all all |   COBOL_ReportNextGroup: "NEXT" "GROUP" "PLUS" COBOL_Number
100 all all all all all all 2.64 COBOL_ReportLine: COBOL_Level "LINE" ["IS"] ["PLUS"] [COBOL_Number] '.' COBOL_ColumnLine*
264 all 5% all all all all 1.05 all |   COBOL_ColumnLine: COBOL_Level [COBOL_ReportLine_Definition] "COLUMN" [COBOL_Number] ("PIC"|"PICTURE") COBOL_Picture COBOL_ColumnLineClause* '.'
277 (5% | 25% | 7% | 60% | 3%) |   |   COBOL_ColumnLineClause: (COBOL_ColumnLineGroup | COBOL_ColumnLineSource | COBOL_ColumnLineSum | COBOL_ColumnLineValue | COBOL_SourceClause)
13 all all |   |   |   COBOL_ColumnLineGroup: "GROUP" "INDICATE"
70 all all 23% |   |   |   COBOL_ColumnLineSource: "SOURCE" COBOL_Identifier_Reference [COBOL_Subscript]
19 all all |   |   |   COBOL_ColumnLineSum: "SUM" COBOL_Identifier_Reference
166 all all all |   |   |   COBOL_ColumnLineValue: "VALUE" ["ALL"] COBOL_Literal
9 all all |   |   |   COBOL_SourceClause: "SOURCE" "PAGE-COUNTER"
767 all all all 54.86 COBOL_ScreenSection: "SCREEN" "SECTION" '.' COBOL_CopyOrScreenDeclaration*
42,076 (6% | 4% | 90%) |   COBOL_CopyOrScreenDeclaration: (COBOL_Copy_Directive | COBOL_Comment | COBOL_ScreenDeclaration)
42,159 all all all |   COBOL_ScreenDeclaration: COBOL_Level COBOL_ScreenContext '.'
176,138 (0% | 0% | 11% | 0% | 0% | 10% | 20% | 14% | 15% | 12% | 8% | none | 2% | 0% | 6% | none) |   |   COBOL_ScreenClause: (COBOL_Comment | COBOL_Literal | ("AUTO"|"BLINK"|"HIGHLIGHT"|"NO-ECHO"|"REVERSE-VIDEO"|"SECURE") | COBOL_ScreenBlankScreen | COBOL_ScreenBlankWhenZero | COBOL_ScreenLine | COBOL_ScreenColumn | COBOL_BackgroundColor | COBOL_ForegroundColor | COBOL_ScreenValue | COBOL_ScreenPicture | COBOL_ScreenPictureVariable | COBOL_ScreenFrom | COBOL_ScreenTo | COBOL_ScreenUsing | COBOL_ScreenPrompt)
42,159 (87% | 13%) |   |   COBOL_ScreenContext: (COBOL_ScreenClauses | COBOL_ScreenName)
36,621 4.80 |   |   |   COBOL_ScreenClauses: COBOL_ScreenClause*
5,538 all 7.00(1%) |   |   |   COBOL_ScreenName: COBOL_ScreenFieldName [COBOL_ScreenClause]*
5,538 (none | all) |   |   COBOL_ScreenFieldName: ("FILLER" | COBOL_Data_Definition)
8,524 98% 6.44 COBOL_Section: [COBOL_SectionHeader] COBOL_Paragraph*
8,343 all all 52% all |   COBOL_SectionHeader: COBOL_Section_Definition "SECTION" [COBOL_Number] '.'
370,739 1.01 100% 0% COBOL_Sentence: COBOL_StatementOrComment* ['.'] ['.']
775 all all 2.72 100% COBOL_SpecialNames: "SPECIAL-NAMES" '.' COBOL_SpecialName* ['.']
2,108 (0% | 0% | 37% | 31% | 0% | 32%) |   COBOL_SpecialName: (COBOL_SpecialNameCallConvention | COBOL_SpecialNameClass | COBOL_SpecialNameConsole | COBOL_SpecialNameCrtStatus | COBOL_SpecialNameCurrency | COBOL_SpecialNameCursor)
1 all all all all |   |   COBOL_SpecialNameCallConvention: "CALL-CONVENTION" COBOL_Number "IS" ("STATICCOBOL"|"STATICW32API"|"WINAPI")
2 all all all 5.00 |   |   COBOL_SpecialNameClass: "CLASS" COBOL_Identifier_Reference "IS" COBOL_SpecialNameClassValue*
6 all all none |   |   |   COBOL_SpecialNameClassValue: COBOL_Expression ["THRU"] [COBOL_Expression]
771 all all all |   |   COBOL_SpecialNameConsole: "CONSOLE" "IS" "CRT"
656 all all all all |   |   COBOL_SpecialNameCrtStatus: "CRT" "STATUS" "IS" COBOL_Identifier_Reference
4 all all all all |   |   COBOL_SpecialNameCurrency: "CURRENCY" "SIGN" "IS" COBOL_Literal
674 all all all |   |   COBOL_SpecialNameCursor: "CURSOR" "IS" COBOL_Identifier_Reference
591,186 (1% | 4% | 2% | 0% | 1% | 0% | 1% | 0% | 2% | 0% | 6% | 0% | 2% | 0% | 0% | 9% | 0% | 15% | 0% | 0% | 0% | 0% | 0% | 40% | 0% | 0% | 1% | 11% | 0% | 0% | 0% | 0% | 0% | 0% | 0% | 0% | 0% | 0% | 1% | 0% | 0% | 0% | 0% | 1%) COBOL_Statement: (COBOL_AcceptStatement | COBOL_AddStatement | COBOL_CallStatement | COBOL_CancelStatement | COBOL_CloseStatement | COBOL_CommitStatement | COBOL_ComputeStatement | COBOL_ContinueStatement | COBOL_CopyStatement | COBOL_DeleteStatement | COBOL_DisplayStatement | COBOL_DivideStatement | COBOL_ExitStatement | COBOL_EvaluateStatement | COBOL_GenerateStatement | COBOL_GoStatement | COBOL_GoBackStatement | COBOL_IfStatement | COBOL_InitiateStatement | COBOL_InitializeStatement | COBOL_InvokeStatement | COBOL_InspectStatement | COBOL_MergeStatement | COBOL_MoveStatement | COBOL_MultiplyStatement | COBOL_NextStatement | COBOL_OpenStatement | COBOL_PerformStatement | COBOL_ReadStatement | COBOL_ReleaseStatement | COBOL_ReturnStatement | COBOL_RewriteStatement | COBOL_SearchStatement | COBOL_SetStatement | COBOL_SortStatement | COBOL_StartStatement | COBOL_StopStatement | COBOL_StringStatement | COBOL_SubtractStatement | COBOL_TerminateStatement | COBOL_UnlockStatement | COBOL_UnstringStatement | COBOL_UseStatement | COBOL_WriteStatement)
600,922 (2% | 98%) COBOL_StatementOrComment: (COBOL_Comment | COBOL_Statement)
44,491 all all all COBOL_Subscript: '(' COBOL_SubscriptType ')'
44,487 all 1% |   COBOL_RegularSubscript: COBOL_Expression [COBOL_SubscriptRange]
392 all all |   |   COBOL_SubscriptRange: (":"|",") COBOL_Expression
44,491 (0% | 100%) |   COBOL_SubscriptType: ("ALL" | COBOL_RegularSubscript)
77 (none | 45% | 55%) COBOL_Type: (COBOL_TypeType | COBOL_ObjectReference | ("1-RECTL"|"2SIZE"|"BINARY-LONG"|"BYTE"|"CLIPFORMAT"|"CLSID"|"DATA-POINTER"|"DWORD"|"FILETIME"|"FLOAT-LONG"|"FORMATETC"|"IID"|"LONG"|"POINT"|"POINTER"|"PROCEDURE-POINTER"|"TAGMSG"|"TAGPOINT"|"TAGRECT"|"TAGSIZE"|"UINT"|"ULARGE-INTEGER"|"ULONG"|"USHORT"|"VARTYPE"|"WORD"|"WRAPPED-BYTE"))
    |   COBOL_TypeType: "TYPE" COBOL_Literal
298,235 (100% | 0%) COBOL_Variable: (COBOL_UserVariable | ("RETURN-CODE"))
298,224 all 1.00(9%) none |   COBOL_UserVariable: COBOL_Modifiable_Identifier [COBOL_Subscript]* [COBOL_OfVariable]*
    |   |   COBOL_OfVariable: "OF" COBOL_Identifier_Reference
934 all all all 44.84 COBOL_WorkingStorage: "WORKING-STORAGE" "SECTION" '.' COBOL_CopyOrDataDeclaration*
234,836 (6% | 94%) |   COBOL_CopyOrDataDeclaration: (COBOL_Copy_Directive | COBOL_DataDeclaration)
4,183 all all all COBOL_AdditiveExpression: COBOL_Expression ("+"|"-") COBOL_Expression
6 all all all COBOL_AddressExpression: "ADDRESS" ["OF"] COBOL_Variable
47,061 all COBOL_BuiltIn: ("ANY"|"FALSE"|"HIGH-VALUES"|"LINAGE-COUNTER"|"LOW-VALUES"|"QUOTE"|"RETURN-CODE"|"SPACE"|"SPACES"|"TRUE"|"ZERO"|"ZEROES"|"ZEROS")
293 all all all all COBOL_ClassCondition: COBOL_Expression ["IS"] ["NOT"] ("ALPHABETIC"|"ALPHABETIC-LOWER"|"ALPHABETIC-UPPER"|"NEGATIVE"|"NUMERIC"|"POSITIVE"|"ZERO")
21 all all all COBOL_ConcatenateExpression: COBOL_Expression '&' COBOL_Expression
1 all all all COBOL_ExponentExpression: COBOL_Expression "**" COBOL_Expression
2 all all all COBOL_IsType: COBOL_Expression "IS" COBOL_Expression
193 all all all COBOL_LengthExpression: "LENGTH" ["OF"] COBOL_Expression
7 all all all COBOL_LinageCounterExpression: "LINAGE-COUNTER" "OF" COBOL_Expression
2,745 all all 23% all COBOL_LogicalAndCondition: COBOL_Expression "AND" [COBOL_RelationalOperator] COBOL_Expression
6,892 all all COBOL_LogicalNotCondition: "NOT" COBOL_Expression
12,015 all all 4% all COBOL_LogicalOrCondition: COBOL_Expression "OR" [COBOL_RelationalOperator] COBOL_Expression
5,161 all all all COBOL_MultiplicativeExpression: COBOL_Expression ("*"|"/") COBOL_Expression
18,758 all all all COBOL_ParenthesizedExpression: '(' COBOL_Expression ')'
90,214 all all all all all COBOL_RelationCondition: COBOL_Expression ["IS"] ["NOT"] COBOL_RelationalOperator COBOL_Expression
    COBOL_SignedExpression: '-' COBOL_Expression
34 all all all COBOL_ThroughExpression: COBOL_Expression "THRU" COBOL_Expression
324,588 all COBOL_VariableExpression: COBOL_VariableRef
324,588 all 1.00(5%) 1.00(0%) |   COBOL_VariableRef: COBOL_Identifier_Reference [COBOL_Subscript]* [COBOL_OfVariableRef]*
1 all all |   |   COBOL_OfVariableRef: "OF" COBOL_Identifier_Reference
76 all all 83% COBOL_ExpressionFunction: "FUNCTION" COBOL_FunctionName [COBOL_FunctionArgs]
63 all 1.32 all |   COBOL_FunctionArgs: '(' COBOL_FunctionParameter* ')'
76 (88% | 12%) |   COBOL_FunctionName: (("CURRENT-DATE"|"INTEGER-OF-DATE"|"LENGTH"|"LOWER-CASE"|"ORD-MAX"|"ORD-MIN"|"RANDOM"|"REM"|"REVERSE"|"TRIM"|"UPPER-CASE") | COBOL_Variable)
83 all 5% all 8% |   COBOL_FunctionParameter: COBOL_Expression [COBOL_ExpressionFunctionRange] [("LEADING"|"TRAILING")] [',']
4 all all |   |   COBOL_ExpressionFunctionRange: ':' COBOL_Expression
4 all all all all all COBOL_LengthFunction: "FUNCTION" "LENGTH" '(' COBOL_Expression ')'
    COBOL_TrimFunction: "FUNCTION" "TRIM" '(' COBOL_Expression [("LEADING"|"TRAILING")] ')'
664 all all all COBOL_BlankWhenZero: "BLANK" ["WHEN"] "ZERO"
35 all all 9% COBOL_ObjectReference: "OBJECT" "REFERENCE" [COBOL_Identifier_Reference]
174,533 all all COBOL_PictureClause: ("PIC"|"PICTURE") COBOL_Picture
13,752 all all COBOL_RedefinesClause: "REDEFINES" COBOL_Identifier_Reference
4 all all all 75% COBOL_RenamesClause: "RENAMES" COBOL_Identifier_Reference ["THRU"] [COBOL_Identifier_Reference]
7 all all all COBOL_Sign: "SIGN" "TRAILING" "SEPARATE"
22 all 1.00 COBOL_ThruClause: "THRU" COBOL_Picture_Value*
    COBOL_Typedef: ["IS"] "TYPEDEF"
41,942 all all all COBOL_Usage: ["USAGE"] ["IS"] ("BINARY"|"COMP"|"COMP-0"|"COMP-1"|"COMP-3"|"COMP-5"|"COMP-X"|"COMPUTATIONAL"|"DISPLAY"|"PACKED-DECIMAL")
25,599 all all all 1.01 COBOL_ValueClause: ("VALUE"|"VALUES") [("ARE"|"IS")] ["ALL"] COBOL_Picture_Value*
24,745 all 100% COBOL_BackgroundColor: "BACKGROUND-COLOR" [COBOL_NumberOrIdentifier]
27,244 all all COBOL_ForegroundColor: "FOREGROUND-COLOR" [COBOL_NumberOrIdentifier]
69,191 (100% | 0%) COBOL_NumberOrIdentifier: (COBOL_Number | COBOL_Identifier_Reference)
84 all all COBOL_ScreenBlankScreen: "BLANK" ("SCREEN"|"LINE")
88 all all all COBOL_ScreenBlankWhenZero: "BLANK" ["WHEN"] "ZERO"
35,743 all 100% COBOL_ScreenColumn: ("COLUMN"|"COL") [COBOL_Number]
3,907 all all 18% COBOL_ScreenFrom: "FROM" COBOL_Identifier_Reference [COBOL_Subscript]
17,203 all all all COBOL_ScreenLine: "LINE" ['+'] COBOL_NumberOrIdentifier
14,578 all all COBOL_ScreenPicture: ("PIC"|"PICTURE") COBOL_Picture
    COBOL_ScreenPictureVariable: ("PIC"|"PICTURE") "X" '(' COBOL_Expression ')'
    COBOL_ScreenPrompt: "PROMPT" COBOL_Literal
10 all all none COBOL_ScreenTo: "TO" COBOL_Identifier_Reference [COBOL_Subscript]
10,658 all 100% 1% COBOL_ScreenUsing: "USING" [COBOL_Identifier_Reference] [COBOL_Subscript]
21,950 all 100% COBOL_ScreenValue: "VALUE" [COBOL_Literal]
7,014 all 2% all 2% 1.96(79%) COBOL_AcceptStatement: "ACCEPT" [COBOL_AcceptPosition] COBOL_Identifier_Reference [COBOL_Subscript] [COBOL_AcceptOption]*
10,798 (42% | 0% | 0% | 7% | 29% | 21%) |   COBOL_AcceptOption: (COBOL_AcceptAt | COBOL_AcceptColumn | COBOL_AcceptCommand | COBOL_AcceptFrom | COBOL_AcceptWithColors | ("AUTO"|"AUTO-SKIP"|"FULL"|"NO-ECHO"|"PROMPT"|"SECURE"|"UPDATE"))
4,576 all all all |   |   COBOL_AcceptAt: "AT" ["LINE"] COBOL_Expression
25 all all |   |   COBOL_AcceptColumn: "COLUMN" COBOL_Expression
6 all all |   |   COBOL_AcceptCommand: "FROM" "COMMAND-LINE"
766 all all all |   |   COBOL_AcceptFrom: "FROM" ("DATE"|"DAY"|"TIME") [("YYYYMMDD"|"YYYYDDD")]
3,172 all all 2.56 |   |   COBOL_AcceptWithColors: "WITH" ["UPDATE"] COBOL_AcceptColor*
8,132 all 65% |   |   |   COBOL_AcceptColor: ("AUTO"|"AUTO-SKIP"|"FOREGROUND-COLOR"|"BACKGROUND-COLOR"|"HIGHLIGHT") [COBOL_Number]
159 all all all all all |   COBOL_AcceptPosition: '(' COBOL_Expression ',' COBOL_Expression ')'
21,447 all all 2.00(0%) all COBOL_AddStatement: "ADD" COBOL_AddType [COBOL_AddOnSizeError]* ["END-ADD"]
2,488 3% all |   COBOL_AddMoreExprs: [','] COBOL_Expression
5,692 0% all |   COBOL_AddMoreVars: [','] COBOL_Variable
19,073 all none all |   COBOL_AddNoGiving: COBOL_Expression [COBOL_AddMoreExprs]* [COBOL_AddTo]
19,073 all all 1.72(17%) |   |   COBOL_AddTo: ["TO"] COBOL_Variable [COBOL_AddMoreVars]*
2 all all all all 1.00 |   COBOL_AddOnSizeError: ["NOT"] "ON" "SIZE" "ERROR" COBOL_Statement*
21,447 (11% | 89%) |   COBOL_AddType: (COBOL_AddWithGiving | COBOL_AddNoGiving)
2,374 all 1.05(100%) all 0% 0% all 1.00 |   COBOL_AddWithGiving: COBOL_Expression [COBOL_AddMoreExprs]* ["TO"] [COBOL_Expression] [','] "GIVING" COBOL_Variable*
9,687 all all all all 2.18(71%) 24% 1.00(1%) all COBOL_CallStatement: "CALL" [("STATICCOBOL"|"WINAPI")] COBOL_CallWhat ["USING"] [COBOL_CallParameter]* [COBOL_CallReturning] [COBOL_CallException]* ["END-CALL"]
93 all all all 1.71 |   COBOL_CallException: ["NOT"] "ON" "EXCEPTION" COBOL_Statement*
15,027 18% all all all 0% |   COBOL_CallParameter: [','] ["BY"] [("CONTENT"|"REFERENCE"|"VALUE")] COBOL_Expression [COBOL_ValueSize]
3 all all |   |   COBOL_ValueSize: "SIZE" COBOL_Number
2,281 all all |   COBOL_CallReturning: "RETURNING" COBOL_Modifiable_Identifier
9,687 (28% | 72% | 1%) |   COBOL_CallWhat: (COBOL_Literal | COBOL_HexNumber | COBOL_Identifier_Reference)
228 all all COBOL_CancelStatement: "CANCEL" COBOL_CancelWhat
228 (67% | 33%) |   COBOL_CancelWhat: (COBOL_Literal | COBOL_Identifier_Reference)
3,636 all all 1.69(66%) COBOL_CloseStatement: "CLOSE" ["RECOVER"] [COBOL_CloseFileList]*
4,025 0% 1% all |   COBOL_CloseFileList: [COBOL_Comment] [','] COBOL_Identifier_Reference
861 all COBOL_CommitStatement: "COMMIT"
4,227 all all 7% all all all COBOL_ComputeStatement: "COMPUTE" COBOL_Modifiable_Identifier [COBOL_Subscript] ["ROUNDED"] '=' COBOL_Expression
6 all COBOL_ContinueStatement: "CONTINUE"
41,502 all all 0% 0% COBOL_CopyStatement: "COPY" COBOL_FileNameOrLiteral [COBOL_CopyIn] [COBOL_CopyReplacing]
1 all all |   COBOL_CopyIn: "IN" COBOL_Identifier_Reference
13 all 1.00 |   COBOL_CopyReplacing: "REPLACING" COBOL_CopyReplace*
13 all all all |   |   COBOL_CopyReplace: COBOL_Expression "BY" COBOL_Expression
41,502 (100% | 0%) |   COBOL_FileNameOrLiteral: (COBOL_FileName | COBOL_Literal)
266 all all all 1.00(1%) all COBOL_DeleteStatement: "DELETE" COBOL_Identifier_Reference ["RECORD"] [COBOL_DeleteInvalidKey]* ["END-DELETE"]
3 all all all 1.33 |   COBOL_DeleteInvalidKey: ["NOT"] "INVALID" "KEY" COBOL_Statement*
56,251 (44% | none | none | none | 56% | 0% | 0% | none | none | none) COBOL_DisplayOptions: (COBOL_DisplayAt | COBOL_DisplayLines | COBOL_DisplaySize | COBOL_DisplayUpon | COBOL_DisplayWith | COBOL_DisplayWithControl | COBOL_DisplayWithNoAdvancing | COBOL_DisplayLine | COBOL_DisplayColumn | ',')
24,592 all 5% 1% |   COBOL_DisplayAt: "AT" [COBOL_DisplayLine] [COBOL_DisplayColumn]
    |   COBOL_DisplayLines: "LINES" COBOL_Expression
    |   COBOL_DisplaySize: "SIZE" COBOL_Expression
    |   COBOL_DisplayUpon: "UPON" COBOL_Identifier_Reference
31,479 all 1.84 |   COBOL_DisplayWith: "WITH" COBOL_DisplayColor*
58,043 all 85% |   |   COBOL_DisplayColor: ("FOREGROUND-COLOR"|"BACKGROUND-COLOR"|"HBCKGROUND-COLOR"|"HIGHLIGHT"|"REVERSE-VIDEO") [COBOL_Number]
84 all all all |   COBOL_DisplayWithControl: "WITH" "CONTROL" COBOL_Identifier_Reference
96 all all all |   COBOL_DisplayWithNoAdvancing: ["WITH"] "NO" "ADVANCING"
36,178 all 5% 2.15 COBOL_DisplayStatement: "DISPLAY" [COBOL_DisplayPosition] COBOL_DisplayClause*
77,856 all 1.00(72%) |   COBOL_DisplayClause: COBOL_DisplayWhat [COBOL_DisplayOptions]*
228 all all |   COBOL_DisplayColumn: "COLUMN" COBOL_Expression
1,267 all all |   COBOL_DisplayLine: "LINE" COBOL_Expression
1,696 all 75% all all all |   COBOL_DisplayPosition: '(' [COBOL_Expression] ',' COBOL_Expression ')'
77,856 1.00 |   COBOL_DisplayWhat: COBOL_Expression*
532 all all 70% all COBOL_DivideStatement: "DIVIDE" COBOL_DivideType [COBOL_DivideRemainder] ["ROUNDED"]
374 all all |   COBOL_DivideRemainder: "REMAINDER" COBOL_Variable
532 (none | 7% | 93%) |   COBOL_DivideType: (COBOL_DivideNoGivingBy | COBOL_DivideNoGivingInto | COBOL_DivideWithGiving)
    |   |   COBOL_DivideNoGivingBy: COBOL_Variable "BY" COBOL_Expression
39 all all all |   |   COBOL_DivideNoGivingInto: COBOL_Expression "INTO" COBOL_Variable
493 all all all all all |   |   COBOL_DivideWithGiving: COBOL_Expression ("BY"|"INTO") COBOL_Expression "GIVING" COBOL_Variable
2,275 all all 2.96(2%) 1.50(0%) 4.03 all COBOL_EvaluateStatement: "EVALUATE" COBOL_EvaluateWhat [COBOL_Comment]* [COBOL_EvaluateAlsoClause]* COBOL_EvaluateWhenClause* ["END-EVALUATE"]
82 all all |   COBOL_EvaluateAlsoClause: "ALSO" COBOL_EvaluateWhat
11,531 (84% | none | none | 16%) |   COBOL_EvaluateWhat: (COBOL_EvaluateCondition | COBOL_EvaluateExpression | COBOL_Identifier_Reference | "OTHER")
9,679 all |   |   COBOL_EvaluateCondition: COBOL_Expression
    |   |   COBOL_EvaluateExpression: COBOL_Expression [COBOL_EvaluateThru]
    |   |   |   COBOL_EvaluateThru: "THRU" COBOL_Expression
9,174 all all 1.65(1%) 1.58(88%) |   COBOL_EvaluateWhenClause: "WHEN" COBOL_EvaluateWhat [COBOL_EvaluateAlsoClause]* [COBOL_StatementOrComment]*
9,167 all all COBOL_ExitStatement: "EXIT" [("PROGRAM"|"PERFORM")]
11 all all COBOL_GenerateStatement: "GENERATE" COBOL_Identifier_Reference
10 all COBOL_GoBackStatement: "GOBACK"
54,660 all all 100% COBOL_GoStatement: "GO" ["TO"] [COBOL_Identifier_Reference]
91,346 all all all 1.89 35% all COBOL_IfStatement: "IF" COBOL_Expression ["THEN"] COBOL_StatementOrComment* [COBOL_Else] ["END-IF"]
31,765 all 1.27 |   COBOL_Else: "ELSE" COBOL_StatementOrComment*
1,586 all all COBOL_InitializeStatement: "INITIALIZE" COBOL_Identifier_Reference
11 all all COBOL_InitiateStatement: "INITIATE" COBOL_Identifier_Reference
1,016 all all all COBOL_InspectStatement: "INSPECT" COBOL_Expression COBOL_InspectType
1,016 (0% | 99% | 1%) |   COBOL_InspectType: (COBOL_InspectConverting | COBOL_InspectReplacing | COBOL_InspectTallying)
3 all all all all |   |   COBOL_InspectConverting: "CONVERTING" COBOL_InspectConvert "TO" COBOL_InspectConvert
6 (33% | 67%) |   |   |   COBOL_InspectConvert: (COBOL_Literal | ("LOWER-CASE"|"LowerCase"|"UPPER-CASE"|"UpperCase"))
1,001 all 1.00 |   |   COBOL_InspectReplacing: "REPLACING" COBOL_InspectReplacePattern*
1,004 all all all all |   |   |   COBOL_InspectReplacePattern: ("ALL"|"FIRST"|"LEADING") COBOL_Expression "BY" COBOL_Expression
12 all 1.08 |   |   COBOL_InspectTallying: "TALLYING" COBOL_InspectTally*
13 (15% | 31% | 15% | 38%) |   |   |   COBOL_InpsectTallyingWhat: (COBOL_InspectTallyingAllExpr | COBOL_InspectTallyingAllLiterals | COBOL_InspectTallyingCharacters | COBOL_InspectTallyingSpaces)
2 all all |   |   |   |   COBOL_InspectTallyingAllExpr: "ALL" COBOL_Expression
4 all 7.00 |   |   |   |   COBOL_InspectTallyingAllLiterals: "ALL" COBOL_Literal*
2 all all all all |   |   |   |   COBOL_InspectTallyingCharacters: "CHARACTERS" "BEFORE" "INITIAL" COBOL_Expression
5 all all |   |   |   |   COBOL_InspectTallyingSpaces: "LEADING" "SPACES"
13 all all all |   |   |   COBOL_InspectTally: COBOL_Identifier_Reference "FOR" COBOL_InpsectTallyingWhat
124 all all all 43% 44% COBOL_InvokeStatement: "INVOKE" COBOL_Identifier_Reference COBOL_Literal [COBOL_InvokeUsing] [COBOL_InvokeReturning]
54 all all |   COBOL_InvokeReturning: "RETURNING" COBOL_Identifier_Reference
53 all 40% all 23% 1.20(19%) |   COBOL_InvokeUsing: "USING" [COBOL_InvokeBy] COBOL_Expression [COBOL_InvokeSize] [COBOL_InvokeMoreUsing]*
21 all all |   |   COBOL_InvokeBy: "BY" ("CONTENT"|"REFERENCE"|"VALUE")
12 all none all none |   |   COBOL_InvokeMoreUsing: [','] [COBOL_InvokeBy] COBOL_Expression [COBOL_InvokeSize]
12 all all |   |   COBOL_InvokeSize: "SIZE" COBOL_Number
2 all all all all all all none 2.00 COBOL_MergeStatement: "MERGE" COBOL_Identifier_Reference "ON" "ASCENDING" ["KEY"] COBOL_Identifier_Reference [COBOL_MergeKey]* COBOL_MergeEntry*
4 (50% | 25% | 25%) |   COBOL_MergeEntry: (COBOL_MergeUsing | COBOL_MergeGiving | COBOL_MergeOutput)
1 all all |   COBOL_MergeGiving: "GIVING" COBOL_Identifier_Reference
    |   COBOL_MergeKey: [','] COBOL_Identifier_Reference
1 all all all all |   COBOL_MergeOutput: "OUTPUT" "PROCEDURE" "IS" COBOL_Identifier_Reference
2 all all 2.00(all) |   COBOL_MergeUsing: "USING" COBOL_Identifier_Reference [COBOL_MergeMoreUsing]*
4 all all |   |   COBOL_MergeMoreUsing: [','] COBOL_Identifier_Reference
237,104 all all all all 100% 2.04(5%) 0% COBOL_MoveStatement: "MOVE" ["ALL"] COBOL_Expression "TO" [COBOL_Variable] [COBOL_MoveMore]* [',']
23,905 0% 5.00(0%) all none |   COBOL_MoveMore: [','] [COBOL_Comment]* COBOL_Variable [COBOL_Subscript]
1,580 all all all 0% COBOL_MultiplyStatement: "MULTIPLY" COBOL_MultiplyType ["ROUNDED"] [COBOL_MultiplyOnSizeError]
1 all all all 1.00 |   COBOL_MultiplyOnSizeError: "ON" "SIZE" "ERROR" COBOL_Statement*
1,580 (11% | 89%) |   COBOL_MultiplyType: (COBOL_MultiplyNoGiving | COBOL_MultiplyWithGiving)
173 all all all |   |   COBOL_MultiplyNoGiving: COBOL_Expression "BY" COBOL_Variable
1,407 all all all all all 1.00(2%) |   |   COBOL_MultiplyWithGiving: COBOL_Expression "BY" COBOL_Expression "GIVING" COBOL_Variable [COBOL_MultiplyMoreVars]*
28 none all |   |   |   COBOL_MultiplyMoreVars: [','] COBOL_Variable
35 all all COBOL_NextStatement: "NEXT" "SENTENCE"
4,631 all all all 3.18(6%) all COBOL_OpenStatement: "OPEN" ("I-O"|"INPUT"|"OUTPUT"|"EXTEND") COBOL_Identifier_Reference [COBOL_OpenFileList]* ["LOCK"]
855 none all |   COBOL_OpenFileList: [','] COBOL_Identifier_Reference
988 (91% | 9%) COBOL_PerformClause: (COBOL_PerformUntil | COBOL_PerformVarying)
898 all all |   COBOL_PerformUntil: "UNTIL" COBOL_Expression
90 all all all all all all |   COBOL_PerformVarying: ("VARYING"|"AFTER") COBOL_Modifiable_Identifier "FROM" COBOL_Expression "BY" COBOL_Expression
152 1.27(99%) 3.80 COBOL_PerformInline: [COBOL_PerformClause]* COBOL_StatementOrComment*
66,457 all 47% 0% 1.08(1%) COBOL_PerformParagraph: COBOL_Identifier_Reference [COBOL_Paragraph_or_Section_Thru] [COBOL_PerformTestWhen] [COBOL_PerformClause]*
66,663 all 0% 100% all COBOL_PerformStatement: "PERFORM" [COBOL_PerformTestWhen] [COBOL_PerformWhat] ["END-PERFORM"]
31,327 all all |   COBOL_Paragraph_or_Section_Thru: ("THRU"|"THROUGH") COBOL_Identifier_Reference
14 all all all |   COBOL_PerformTestWhen: ["WITH"] "TEST" ("BEFORE"|"AFTER")
66,656 (0% | 0% | 0% | 100% | 0%) |   COBOL_PerformWhat: (COBOL_PerformNothing | COBOL_PerformTimes | COBOL_PerformTimesInline | COBOL_PerformParagraph | COBOL_PerformInline)
2 2.00 |   |   COBOL_PerformNothing: COBOL_PerformClause*
40 all 18% all all |   |   COBOL_PerformTimes: COBOL_Identifier_Reference [COBOL_Paragraph_or_Section_Thru] COBOL_Expression "TIMES"
5 all all 5.20 |   |   COBOL_PerformTimesInline: COBOL_Number "TIMES" COBOL_StatementOrComment*
2,491 all 1.07 all 1.68(83%) all COBOL_ReadStatement: "READ" COBOL_Identifier_Reference* ["RECORD"] [COBOL_ReadClause]* ["END-READ"]
300 all all 1.02 |   COBOL_ReadAtEndAction: "AT" "END" COBOL_Statement*
3,463 (0% | 12% | 9% | 45% | 34% | 1%) |   COBOL_ReadClause: (COBOL_ReadInto | COBOL_ReadNext | COBOL_ReadAtEndAction | COBOL_ReadIgnoreLock | COBOL_ReadKey | COBOL_ReadInvalidKey)
1,545 all all all |   COBOL_ReadIgnoreLock: ["WITH"] [("IGNORE"|"KEPT")] "LOCK"
6 all all |   COBOL_ReadInto: "INTO" COBOL_Identifier_Reference
30 all all all 1.40 |   COBOL_ReadInvalidKey: ["NOT"] "INVALID" "KEY" COBOL_Statement*
1,177 all all all all |   COBOL_ReadKey: ["WITH"] "KEY" "IS" COBOL_Identifier_Reference
405 all all |   COBOL_ReadNext: "NEXT" ["RECORD"]
14 all all 36% COBOL_ReleaseStatement: "RELEASE" COBOL_Identifier_Reference [COBOL_ReleaseFrom]
5 all all |   COBOL_ReleaseFrom: "FROM" COBOL_Identifier_Reference
14 all all all all COBOL_ReturnStatement: "RETURN" COBOL_Identifier_Reference COBOL_ReturnAtEndAction "END-RETURN"
14 all all 1.00 |   COBOL_ReturnAtEndAction: "AT" "END" COBOL_Statement*
610 all all 1% all COBOL_RewriteStatement: "REWRITE" COBOL_Identifier_Reference [COBOL_RewriteKey] ["END-REWRITE"]
8 all all 1.00 |   COBOL_RewriteKey: "INVALID" "KEY" COBOL_Statement*
25 all all all 96% 1.00 all COBOL_SearchStatement: "SEARCH" ["ALL"] COBOL_Identifier_Reference [COBOL_SearchAtEndAction] COBOL_SearchWhenClause* ["END-SEARCH"]
24 all all 1.21 |   COBOL_SearchAtEndAction: "AT" "END" COBOL_Statement*
25 all all 2.88 |   COBOL_SearchWhenClause: "WHEN" COBOL_Expression COBOL_Statement*
331 all all all all COBOL_SetStatement: "SET" COBOL_Identifier_Reference COBOL_SetHow COBOL_Expression
331 (1% | 99%) |   COBOL_SetHow: (COBOL_SetBy | COBOL_SetTo)
3 all all |   |   COBOL_SetBy: "UP" "BY"
328 all all |   |   COBOL_SetTo: "TO" ["ENTRY"]
20 all all all all all all 1.00(15%) 70% 10% 30% 50% COBOL_SortStatement: "SORT" COBOL_Identifier_Reference "ON" ("ASCENDING"|"DESCENDING") ["KEY"] COBOL_Identifier_Reference [COBOL_SortKey]* [COBOL_SortInput] [COBOL_SortUsing] [COBOL_SortOutput] [COBOL_SortGiving]
10 all all |   COBOL_SortGiving: "GIVING" COBOL_Identifier_Reference
14 all all all all |   COBOL_SortInput: "INPUT" "PROCEDURE" "IS" COBOL_Identifier_Reference
3 67% all |   COBOL_SortKey: [','] COBOL_Identifier_Reference
6 all all all all |   COBOL_SortOutput: "OUTPUT" "PROCEDURE" "IS" COBOL_Identifier_Reference
2 all all |   COBOL_SortUsing: "USING" COBOL_Identifier_Reference
569 all all all all all 2% all COBOL_StartStatement: "START" COBOL_Identifier_Reference "KEY" COBOL_StartRelOp COBOL_Identifier_Reference [COBOL_StartInvalid] ["END-START"]
12 all all 1.00 |   COBOL_StartInvalid: "INVALID" "KEY" COBOL_Statement*
569 (2% | 0% | 98%) |   COBOL_StartRelOp: (COBOL_StartOper2 | COBOL_StartOper3 | ("<="|">="|"<"|">"))
11 all all all |   |   COBOL_StartOper2: "IS" "GREATER" "THAN"
1 all all all |   |   COBOL_StartOper3: "IS" "EQUAL" "TO"
2,266 all all COBOL_StopStatement: "STOP" "RUN"
1,646 all 3.09 all 1.00 0% all COBOL_StringStatement: "STRING" COBOL_StringWhat* "INTO" COBOL_StringPiece* [COBOL_StringWith] ["END-STRING"]
2 all all |   COBOL_StringDelimitSpaces: ["ALL"] ("SPACE"|"SPACES")
1,646 none all none |   COBOL_StringPiece: [','] COBOL_Identifier_Reference [COBOL_StringCount]
    |   |   COBOL_StringCount: "COUNT" "IN" COBOL_Identifier_Reference
5,091 all 100% |   COBOL_StringWhat: COBOL_Expression [COBOL_StringDelimited]
5,089 all all all |   |   COBOL_StringDelimited: "DELIMITED" ["BY"] COBOL_StringDelimitByWhat
5,089 (71% | 0% | 29% | 0%) |   |   |   COBOL_StringDelimitByWhat: ("SIZE" | COBOL_HexNumber | COBOL_Literal | COBOL_StringDelimitSpaces)
4 all all all |   COBOL_StringWith: "WITH" "POINTER" COBOL_Identifier_Reference
6,776 all all all all all COBOL_SubtractStatement: "SUBTRACT" COBOL_Expression "FROM" COBOL_SubtractType ["ROUNDED"]
783 none all |   COBOL_SubtractMoreVars: [','] COBOL_Variable
5,900 all 1.59(8%) |   COBOL_SubtractNoGiving: COBOL_Variable [COBOL_SubtractMoreVars]*
6,776 (13% | 87%) |   COBOL_SubtractType: (COBOL_SubtractWithGiving | COBOL_SubtractNoGiving)
876 all none all all 1.00(8%) |   COBOL_SubtractWithGiving: COBOL_Expression [COBOL_SubtractMoreExprs]* "GIVING" COBOL_Variable [COBOL_SubtractMoreVars]*
    |   |   COBOL_SubtractMoreExprs: [','] COBOL_Expression
11 all all COBOL_TerminateStatement: "TERMINATE" COBOL_Identifier_Reference
686 all all COBOL_UnlockStatement: "UNLOCK" COBOL_Identifier_Reference
538 all all 100% all 3.59 1% 97% all COBOL_UnstringStatement: "UNSTRING" COBOL_Expression [COBOL_UnstringDelimited] "INTO" COBOL_UnstringPiece* [COBOL_UnstringWith] [COBOL_Overflow] ["END-UNSTRING"]
537 all all all all 1.01(35%) |   COBOL_UnstringDelimited: "DELIMITED" "BY" ["ALL"] COBOL_UnstringOrWhat [COBOL_UnstringOrClause]*
189 all all all |   COBOL_UnstringOrClause: "OR" ["ALL"] COBOL_UnstringOrWhat
726 (99% | 1%) |   COBOL_UnstringOrWhat: (COBOL_Literal | "SPACES")
1,933 1% all 0% 0% |   COBOL_UnstringPiece: [','] COBOL_Identifier_Reference [COBOL_UnstringCount] [COBOL_UnstringDelimiter]
4 all all all |   |   COBOL_UnstringCount: "COUNT" "IN" COBOL_Identifier_Reference
3 all all all |   |   COBOL_UnstringDelimiter: "DELIMITER" "IN" COBOL_Expression
7 all all all |   COBOL_UnstringWith: "WITH" "POINTER" COBOL_Identifier_Reference
3 all all all all COBOL_UseStatement: "USE" "BEFORE" "REPORTING" COBOL_Identifier_Reference
8,232 all all 2% 74% 0% all COBOL_WriteStatement: "WRITE" COBOL_Identifier_Reference [COBOL_WriteFrom] [COBOL_WriteAfter] [COBOL_WriteKey] ["END-WRITE"]
6,057 all all 96% all |   COBOL_WriteAfter: ("BEFORE"|"AFTER") ["ADVANCING"] [COBOL_Expression] [("PAGE"|"LINE"|"LINES")]
146 all all |   COBOL_WriteFrom: "FROM" COBOL_Expression
19 all all 1.47 |   COBOL_WriteKey: "INVALID" "KEY" COBOL_Statement*

Terminals = 20 (instances=2,290,108)
Tokens = 411 (instances=8,011,908)

(*) Statistics are shown in the same order as the Tokens.
Percentages are rounded; 'all' and 'none' mean 100% and 0% before rounding.
For lists, it shows the average number of occurrences, excluding empty lists.