TypeCobol
TypeCobol copied to clipboard
Type seeking in dependencies files
We are facing a problem does not allow parser to seek for type inside a type contains in a dependencies file.
What we need to do today, is to qualify TYPE DepFile::SITE which is a local type of DepFile.
DepFile PGM CURRENT
01 TechnicalContext TYPEDEF STRICT PUBLIC.
05 TechName PIC X(8).
05 Site TYPE DepFile::SITE.
01 SITE TYPEDEF STRICT PUBLIC.
05 SiteName PIC X(8).
What we want is to be able to not use DepFile:: in front of SITE.
DepFile PGM EXPECTED
01 TechnicalContext TYPEDEF STRICT PUBLIC.
05 TechName PIC X(8).
05 Site TYPE SITE. *> No need to prefix with DepFile:: here
01 SITE TYPEDEF STRICT PUBLIC.
05 SiteName PIC X(8).
Needs to works fine like this :
Source File
01 W-TechCtx TYPE CALLEE::TechnicalContext.
MOVE W-TechCtx::Site::SiteName TO someformat.
Issue has been resolved thanks to issue #754 👍
Need to add a unit test for this issue
A non workingcase has been detected with Procedure call. Procedure have an input parameter like this
param1 TYPE Span
and the given argument when call is of type MyDepFile::Span..
Dep. File
01 Span typedef strict public.
01 SpanArray typedef strict public.
05 span type Span.
declare procedure ToSpan public
input param1 pic X(1)
output spanVar type Span.
end-declare.
Main Pgm
01 SpanArrayVar TYPE Dep::SpanArray
CALL Dep::ToSpan input 1 output SpanArrayVar::span.
This will cause an error on proc call. It's because of line 1028 in SymbolTable.cs.
We will need to implement a QualifiedDataType
, which will contains the pgm name where the DataType is coming from.
Dep File :
IDENTIFICATION DIVISION.
PROGRAM-ID. IRLLBIRL.
AUTHOR. REYDELPA.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SPECIAL-NAMES. DECIMAL-POINT IS COMMA.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 Irl TYPEDEF STRICT PUBLIC.
05 IsinCode PIC X(12).
05 IrlQty TYPE Qty.
01 Qty TYPEDEF STRICT PUBLIC.
05 Dec TYPE TTTLBDEC::Dec.
01 Span TYPEDEF STRICT PUBLIC.
01 SpannArray TYPEDEF STRICT PUBLIC.
05 span TYPE Span.
LINKAGE SECTION.
PROCEDURE DIVISION.
declare procedure ToSpan public
input input1 PIC X(1)
output output1 type Span
.
end-declare.
declare procedure ToSpan public
input input1 PIC X(10)
output output1 type Span
.
end-declare.
END PROGRAM IRLLBIRL.
Source File :
IDENTIFICATION DIVISION.
PROGRAM-ID. PGM.
DATA DIVISION.
Working-STORAGE SECTION.
01 MyPicVar PIC X(10).
01 IRLTest TYPE IRLLBIRL::Irl.
01 MyGroup.
05 IRLQty TYPE IRLLBIRL::Qty.
01 SpanArrayVar TYPE IRLLBIRL::SpannArray.
01 AlphaNum PIC X(01).
PROCEDURE DIVISION.
MOVE MyPicVar TO IRLTest::IrlQty::Dec::I.
MOVE MyGroup::IRLQty::Dec::I TO MyPicVar.
CALL IRLLBIRL::ToSpan INPUT AlphaNum OUTPUT SpanArrayVar::span.
CALL IRLLBIRL::ToSpan INPUT MyPicVar OUTPUT SpanArrayVar::span.
END PROGRAM PGM.
Errors that should not be here :
2 errors in "input\PGM.rdz.tcbl":
Line 16[8,69] <27, Error, Syntax> - Syntax error : No suitable function signature found for 'IRLLBIRL.ToSpan' input(Alphanumeric) output(Span)
Line 17[8,69] <27, Error, Syntax> - Syntax error : No suitable function signature found for 'IRLLBIRL.ToSpan' input(Alphanumeric) output(Span)
Need to see what's happening in TypeCobolChecker.
This should be resolved when issue #1046 is finished because of using clause etc..
Won't fix as TypeCobol language is no longer supported.