Skip to main content

[Migrated content. Thread originally posted on 15 May 2012]

Hi!
I am having an issue retrieving a time field from my SQL table into my COBOL program.
It is defined as a time(7) in my SQL table, so I defined it in COBOL as PIC 9(06)V9999999.
When I perform my get statement, I am receiving a 2002 error which means the field is not formatted correctly.
How should it be formatted correctly so I can get that field back into my program?

[Migrated content. Thread originally posted on 15 May 2012]

Hi!
I am having an issue retrieving a time field from my SQL table into my COBOL program.
It is defined as a time(7) in my SQL table, so I defined it in COBOL as PIC 9(06)V9999999.
When I perform my get statement, I am receiving a 2002 error which means the field is not formatted correctly.
How should it be formatted correctly so I can get that field back into my program?

TIME Data Conversions

The COBOL data item must be:

(1) nonnumeric with a length of 2, 4, 6 or 8 characters; or
(2) numeric with a scale of zero and a precision of 2, 4, 6 or 8 digits.

The COBOL data item will receive (when fetching from database) or must contain (when updating the database) a time in the form HHmmSScc, where HH is a two-digit hour of the day, mm is a two-digit minute of the hour, SS is a two-digit second of the minute and cc is a two-digit centi-second of the second. When the length or precision is 2, only the hours field is present, when 4, only the HHmm fields are present, and so forth.

When transferring data from the data source to the COBOL program, the time value from the data source is stored into the COBOL data item according to the format described for a COBOL time data item. Since SQL time values do not contain centi-seconds, if the COBOL data item includes the cc field, it will always be set to 00. If the COBOL time data item does not include some or all of the time fields, these values are truncated without error. A length indicator value of sql-Null-Data indicates a NULL in the data source; otherwise, the length indicator will be 6 for TIME data.

When transferring data from the COBOL program to the data source, the time value of the COBOL data item is validated and sent to the data source. If the validation fails, an error occurs and the InstantSQL statement is terminated without sending the bad value to the data source. The validation is that HH must be 00-23, mm must be 00-59 and SS must be 00-61. (The range of seconds allows as many as two leap seconds to maintain synchronization of sidereal time.) Since SQL time values do not contain centi-seconds, if the COBOL data item specifies centi-seconds, they will be truncated without error. If the COBOL time data item does not include some or all of the time fields, zeroes are supplied to create the data source time value. To indicate a NULL time, the length indicator value must be set to sql-Null-Data.

[Migrated content. Thread originally posted on 15 May 2012]

Hi!
I am having an issue retrieving a time field from my SQL table into my COBOL program.
It is defined as a time(7) in my SQL table, so I defined it in COBOL as PIC 9(06)V9999999.
When I perform my get statement, I am receiving a 2002 error which means the field is not formatted correctly.
How should it be formatted correctly so I can get that field back into my program?

Bruce,

You might have someone double check that documentation that you cut and pasted into your reply.
I got it to work, but the ONLY way It worked is when the PIC looked like this:

05 GLAUDRPT-SYS-TIME PIC X(16).

The numeric way wouldn't work at all. I hope this doesn't screw up my data when I start writing back to SQL....

[Migrated content. Thread originally posted on 15 May 2012]

Hi!
I am having an issue retrieving a time field from my SQL table into my COBOL program.
It is defined as a time(7) in my SQL table, so I defined it in COBOL as PIC 9(06)V9999999.
When I perform my get statement, I am receiving a 2002 error which means the field is not formatted correctly.
How should it be formatted correctly so I can get that field back into my program?

OK, I'll double check the documentation. Both the numeric and nonnumeric way should work; did you note that using numeric requires an integer (zero scale) data item? If PIC X(16) worked, it sounds more like TIMESTAMP than TIME.

[Migrated content. Thread originally posted on 15 May 2012]

Hi!
I am having an issue retrieving a time field from my SQL table into my COBOL program.
It is defined as a time(7) in my SQL table, so I defined it in COBOL as PIC 9(06)V9999999.
When I perform my get statement, I am receiving a 2002 error which means the field is not formatted correctly.
How should it be formatted correctly so I can get that field back into my program?

Amy,

I checked the documentation against the code and the conversion for time is described correctly in the documentation. A 16-character COBOL data item is not supported for receiving the value of an SQL time data type. Only a 2, 4, 6 or 8 character COBOL data item may be specified to receive a time SQL data type. I believe you have misinterpreted the results of your experiment. A timestamp SQL data type can be fetched into a 16-character COBOL data item; for timestamps, the COBOL data item must have an even length and 8 to 16 characters (see the documentation for more details about conversion to/from the timestamp SQL data type).

If you supply more details of the InstantSQL statements your are using, including the parameters passed and the descriptions of those parameters, I might be able to provide more assistance.

--Bruce

[Migrated content. Thread originally posted on 15 May 2012]

Hi!
I am having an issue retrieving a time field from my SQL table into my COBOL program.
It is defined as a time(7) in my SQL table, so I defined it in COBOL as PIC 9(06)V9999999.
When I perform my get statement, I am receiving a 2002 error which means the field is not formatted correctly.
How should it be formatted correctly so I can get that field back into my program?

I am getting the time field from a stored procedure.
The field in SQL is defined as time(7).


This is my prepare statement to call the Stored procedure:

SQL PREPARE QUERY sql-QueryHandle
sql-ConnectionHandle
"{call GLAudit_FindReport(?,?,?,?,?)}"
IF sql-ok
SQL BIND PARAMETER sql-QueryHandle
1, sql-Integer, sql-Param-Input LINK-FISCAL-CCYY OMITTED
2, sql-Integer, sql-Param-Input WS-SQL-START-DT OMITTED
3, sql-Integer, sql-Param-Input WS-SQL-END-DT OMITTED
4, sql-VarChar, sql-Param-Input, WS-SQL-GL-ACCT OMITTED
5, sql-Integer, sql-Param-Input, WS-FIND-TYPE OMITTED
MOVE ZEROS TO WS-SQL-START-DT
WS-SQL-END-DT
WS-FIND-TYPE
MOVE SPACES TO WS-SQL-GL-ACCT
IF A-OPTION-01 = "X"
MOVE 1 TO WS-FIND-TYPE
MOVE A-START-DATE TO WS-SQL-START-DT
MOVE A-END-DATE TO WS-SQL-END-DT
ELSE
MOVE 2 TO WS-FIND-TYPE
MOVE A-GL-ACCT TO WS-SQL-GL-ACCT
END-IF
SQL START QUERY sql-QueryHandle

My stored procedure looks like this:
USE [GL]
GO
/****** Object: StoredProcedure [dbo].[GLAudit_FindReport] Script Date: 05/17/2012 08:54:53 ******/
SET ANSI_NULLS ON
GO
SET QUOTED_IDENTIFIER ON
GO

ALTER PROCEDURE [dbo].[GLAudit_FindReport]
@FiscalYear int,
@BegDate int,
@EndDate int,
@AcctNum varchar(13),
@RptOption int

-- Report Options
-- 1 = Date Range
-- 2 = Single Account #

AS
BEGIN
SET NOCOUNT ON;

DECLARE @WHERE as nvarchar(4000);
DECLARE @ORDER as nvarchar(4000);

DECLARE @STRSEL as nvarchar(4000);
DECLARE @STRFUL as nvarchar(4000);

--Defaults
SET @ORDER = ' ORDER BY GL.dbo.GLAudit.SystemDate, GL.dbo.GLAudit.SystemTime, GL.dbo.AccountNumbers.AccountNumber'
SET @WHERE = ' WHERE GL.dbo.ChartAccounts.FiscalYear = ' Cast(@FiscalYear as varchar(50))
PRINT @WHERE

IF @RptOption = 1
SET @WHERE = @WHERE ' AND GL.dbo.GLAudit.SystemDate >= ' '''' CAST(@BegDate as varchar(12)) ''''

IF @RptOption = 1
SET @WHERE = @WHERE ' AND GL.dbo.GLAudit.SystemDate

IF @RptOption = 2
SET @WHERE = @WHERE ' AND GL.dbo.AccountNumbers.AccountNumber = ' '''' @AcctNum ''''


SET @STRSEL = '
SELECT GL.dbo.GLAudit.GLAuditID, GL.dbo.GLAudit.SystemDate, GL.dbo.GLAudit.SystemTime, GL.dbo.ChartAccounts.FiscalYear,
GL.dbo.GLAudit.ChartAcctID, GL.dbo.AccountNumbers.AccountNumber, GL.dbo.GLAudit.UserID, MSISystem.dbo.MSIPass.UserName,
GL.dbo.GLAudit.AuditType, GL.dbo.GLAudit.FieldName, GL.dbo.GLAudit.BeforeAlpha, GL.dbo.GLAudit.AfterAlpha,
GL.dbo.GLAudit.BeforeNumeric, GL.dbo.GLAudit.AfterNumeric
FROM GL.dbo.GLAudit
LEFT OUTER JOIN GL.dbo.ChartAccounts ON GL.dbo.GLAudit.ChartAcctID = GL.dbo.ChartAccounts.ChartAcctID
LEFT OUTER JOIN GL.dbo.AccountNumbers ON GL.dbo.ChartAccounts.AcctNumID = GL.dbo.AccountNumbers.AccountNumID
LEFT OUTER JOIN MSISystem.dbo.MSIPass ON GL.dbo.GLAudit.UserID = MSISystem.dbo.MSIPass.MSIPassID'

SET @STRFUL = @STRSEL ISNULL(@WHERE,'') ISNULL(@ORDER,'')

PRINT @STRFUL

EXECUTE sp_executesql @STRFUL


My dates are being passed through as integers because SQL was not allowing me to treat the parameters as dates.

Anyway, then here is my get statement:
SQL GET DATA sql-QueryHandle
"GLAuditID" GLAUDRPT-ID GLAUDRPT-ID-LEN
"SystemDate" GLAUDRPT-SYS-DATE GLAUDRPT-SYS-DATE-LEN
"SystemTime" GLAUDRPT-SYS-TIME GLAUDRPT-SYS-TIME-LEN
"FiscalYear" GLAUDRPT-YEAR GLAUDRPT-YEAR-LEN
"ChartAcctID" GLAUDRPT-CHART-ID GLAUDRPT-CHART-ID-LEN
"AccountNumber" GLAUDRPT-ACCT GLAUDRPT-ACCT-LEN
"UserID" GLAUDRPT-USER-ID GLAUDRPT-USER-ID-LEN
"UserName" GLAUDRPT-USER-NAME GLAUDRPT-USER-NAME-LEN
"AuditType" GLAUDRPT-AUDIT-TYPE GLAUDRPT-AUDIT-TYPE-LEN
"FieldName" GLAUDRPT-FIELD-NAME GLAUDRPT-FIELD-NAME-LEN
"BeforeAlpha" GLAUDRPT-B-ALPHA GLAUDRPT-B-ALPHA-LEN
"AfterAlpha" GLAUDRPT-A-ALPHA GLAUDRPT-A-ALPHA-LEN
"BeforeNumeric" GLAUDRPT-B-NUMERIC GLAUDRPT-B-NUMERIC-LEN
"AfterNumeric" GLAUDRPT-A-NUMERIC GLAUDRPT-A-NUMERIC-LEN.

[Migrated content. Thread originally posted on 15 May 2012]

Hi!
I am having an issue retrieving a time field from my SQL table into my COBOL program.
It is defined as a time(7) in my SQL table, so I defined it in COBOL as PIC 9(06)V9999999.
When I perform my get statement, I am receiving a 2002 error which means the field is not formatted correctly.
How should it be formatted correctly so I can get that field back into my program?

Amy,

Thanks for the information. Could you also post

(1) the name of the data base system (MS SQLServer, MySQL, Oracle, ...?) that you are using.
(2) the COBOL data descriptions for the parameters in the SQL GET DATA statement.
(3) where you get the 2002 error (is it the result of the SQL GET DATA statement?)
(4) Windows or UNIX?

I am not familiar with time(7), which sounds specific to the data base implementation. It's possible this data type does not map to an SQL time (SQL_TIME) data type supported by ODBC.

--Bruce

[Migrated content. Thread originally posted on 15 May 2012]

Hi!
I am having an issue retrieving a time field from my SQL table into my COBOL program.
It is defined as a time(7) in my SQL table, so I defined it in COBOL as PIC 9(06)V9999999.
When I perform my get statement, I am receiving a 2002 error which means the field is not formatted correctly.
How should it be formatted correctly so I can get that field back into my program?

(1) the name of the data base system (MS SQLServer, MySQL, Oracle, ...?) that you are using. - MS SQL Server 2008 R2


(2) the COBOL data descriptions for the parameters in the SQL GET DATA statement.

This is my current one that is working.

01 GLAUDRPT-REC.
05 GLAUDRPT-ID PIC 9(09).
05 GLAUDRPT-SYS-DATE PIC 9(08).
05 GLAUDRPT-SYS-TIME PIC X(16).
05 GLAUDRPT-YEAR PIC 9(04).
05 GLAUDRPT-CHART-ID PIC 9(09).
05 GLAUDRPT-ACCT PIC X(13).
05 GLAUDRPT-USER-ID PIC 9(09).
05 GLAUDRPT-USER-NAME PIC X(40).
05 GLAUDRPT-AUDIT-TYPE PIC X(08).
05 GLAUDRPT-FIELD-NAME PIC X(30).
05 GLAUDRPT-B-ALPHA PIC X(30).
05 GLAUDRPT-A-ALPHA PIC X(30).
05 GLAUDRPT-B-NUMERIC PIC S9(11)V99.
05 GLAUDRPT-A-NUMERIC PIC S9(11)V99.



(3) where you get the 2002 error (is it the result of the SQL GET DATA statement?) I get it after the GET DATA
(4) Windows or UNIX? - Windows


[Migrated content. Thread originally posted on 15 May 2012]

Hi!
I am having an issue retrieving a time field from my SQL table into my COBOL program.
It is defined as a time(7) in my SQL table, so I defined it in COBOL as PIC 9(06)V9999999.
When I perform my get statement, I am receiving a 2002 error which means the field is not formatted correctly.
How should it be formatted correctly so I can get that field back into my program?

Amy,

I am still digesting the information you posted, without finding any definite issues so far.

I looked up time(7) and determined that it's just time that includes fractional seconds to the nearest 100 nanoseconds. InstantSQL uses ODBC 2.x features, which only allows 1 second resolution of time. This shouldn't be related to the problem because InstantSQL tells 3.x ODBC drivers that it expects 2.x results and the driver should return the time with the fractional seconds truncated. Possibly the driver is reporting this truncation incorrectly as an error, but that wouldn't explain why a 16-character item works for receiving the time.

Have you tried using a 6-character item and, if you get the error, using SQL DESCRIBE ERROR (in a loop as shown in the example) to get all the error information? Can you post the error information that you get with SQL DESCRIBE ERROR?

--Bruce

[Migrated content. Thread originally posted on 15 May 2012]

Hi!
I am having an issue retrieving a time field from my SQL table into my COBOL program.
It is defined as a time(7) in my SQL table, so I defined it in COBOL as PIC 9(06)V9999999.
When I perform my get statement, I am receiving a 2002 error which means the field is not formatted correctly.
How should it be formatted correctly so I can get that field back into my program?

This is what it said:

"Data truncation error for result column named SystemTime, which is result column number 3."

[Migrated content. Thread originally posted on 15 May 2012]

Hi!
I am having an issue retrieving a time field from my SQL table into my COBOL program.
It is defined as a time(7) in my SQL table, so I defined it in COBOL as PIC 9(06)V9999999.
When I perform my get statement, I am receiving a 2002 error which means the field is not formatted correctly.
How should it be formatted correctly so I can get that field back into my program?

Amy,

Truncation error is interesting. I don't think that should happen and I believe it's being reported by the ODBC driver to InstantSQL. What value do you get in the PIC X(16), where you say it works? Are the fractional digits shown?

If you can experiment with a time(0), that might work as documented for time conversions in InstantSQL.

--Bruce

[Migrated content. Thread originally posted on 15 May 2012]

Hi!
I am having an issue retrieving a time field from my SQL table into my COBOL program.
It is defined as a time(7) in my SQL table, so I defined it in COBOL as PIC 9(06)V9999999.
When I perform my get statement, I am receiving a 2002 error which means the field is not formatted correctly.
How should it be formatted correctly so I can get that field back into my program?

Amy,

I am beginning to suspect that your stored procedure does not return an SQL_TIME type for column 3 named SystemTime. You could use SQL QUERY PROCEDURE-COLUMNS to get information about the columns returned by your procedure. It's possible the stored procedure is returning an SQL_CHAR or SQL_VARCHAR type. A time(7) value requires 16 characters when represented as a character string (for example, "23:59:59.9999999"). Since it's a fixed length, it's probably a CHAR(16) type, but it could be a VARCHAR(16) type.

Note that SQL QUERY PROCEDURE-COLUMNS returns a result set and you have to fetch the rows of the result set to get the information about the columns of the stored procedure. Each row of the result set describes one column of the stored procedure. The row that has SystemTime in column 4 (column_name) describes the stored procedure column SystemTime). The data_type column of this row contains the column type number and the type_name column contains the column type name. If the column type name is CHAR or VARCHAR, then the stored procedure is converting the time to a character string, so InstantSQL does not see it as a time value.

You should also check to see if your date column(s) are being returned as character strings instead of dates.

--Bruce