From: Rick Smith on 11 Mar 2007 05:31 "William M. Klein" <wmklein(a)nospam.netcom.com> wrote in message news:MsLIh.6139$pj4.2291(a)fe09.news.easynews.com... > Richard, > Are you assuming that "Moded fields" are USAGE BINARY-CHAR - or a "BINARY" > (with non-ANSI "notrunc" behavior). Otherwise, I don't know how you are > processing them. This is part of my problem in "solving" this problem. > Standard COBOL (pre- USAGE BINARY-CHAR) has no way to define a numeric field as > "binary" without truncation. PIC 9(9) BINARY The call to CEE3INF, as I understand it, will return the values untruncated. Since truncation occurs when the COBOL program stores the result of a calculation, I don't see truncation, from the COMPUTE statements, as a problem. The worrisome case appears to be getting bit 0 of a field, such as, the CICS bit from sys/subsys; since this would involve division by +2147483648 (2 ** 31). compute cics-bit = function mod (function integer (sys-subsys / (2 ** 31)) 2) This statement correctly returns either +1 or +0 with ANSI truncation (the default) in effect, on Micro Focus COBOL 3.2.24. ----- $set ibmcomp vsc2 arithmetic"vsc2" identification division. program-id. test3inf. working-storage section. 01 sys-subsys pic 9(9) binary value 0. 01 cics-bit pic s9(4) binary value +0. procedure division. begin. move x"80000000" to sys-subsys (1:4) compute cics-bit = function mod (function integer (sys-subsys / (2 ** 31)) 2) if cics-bit = +1 display "CICS bit is on" end-if goback. ----- > "Rick Smith" <ricksmith(a)mfi.net> wrote in message > news:12v6pek1atd1a64(a)corp.supernews.com... > > > > "William M. Klein" <wmklein(a)nospam.netcom.com> wrote in message > > news:rrDIh.242220$k82.140284(a)fe07.news.easynews.com... > >> to: comp.lang.cobol *and* IBM-MAIN > >> > >> IBM has (relatively) recently created an LE callable service, CEE3INF, > > that > >> returns a "32-bit map" with information about what environment a program > > is > >> running in. See: > >> > >> > > http://publibz.boulder.ibm.com/cgi-bin/bookmgr_OS390/BOOKS/CEEA3170/2.2.5.9 > >> > >> Now, my question is how various "experienced" COBOL programmers would > > handle > >> such information (either in an IBM mainframe environment OR in other COBOL > >> environments for those who see this note and don't work in IBM mainframe > >> environments - but do get "bit maps") > >> > >> 1) Call a non-COBOL program to decode this map (e.g.. Assembler, C, PL/I > > or any > >> other language that can easily handle "bits") > >> > >> 2) Do a "division" loop to figure out which bits are turned on? > >> > >> 3) Use 88-levels with hex literals to check for which bits were turned on? > >> > >> 4) Use the LE (or comparable) "bit manipulation" routines? > >> > >> 5) Not use CEE3INF from COBOL? > >> > >> 6) Other? > >> > >> *** > >> > >> Although I wouldn't LIKE it, I can imagine doing this in any of these > > ways. > >> Obviously, when/if a COBOL compiler supports the '02 Standard Bit/Boolean > >> features, this becomes "trivial". However, as few (if any) compilers do > > this > >> yet, I was wondering how programmers would handle this requirement. > > > > There are a lot of "reserved" bits in the four full-words. > > While some of these may become assigned, it seems > > unlikely that any would be moved. As new bits become > > assigned, a routine that processes all bits, such as a > > "division loop" would, I believe, be more sensitive to > > maintenance than one that extracts the bit fields directly. > > Also one need not extract more than is desired. > > > > Extracting these bit fields directly seems a rather > > straight-forward process with intrinsic functions. The > > exponents below are 31 minus the low-order bit number > > of the field. > > > > ----- > > compute c-bit = function mod > > (function integer (member-id / (2 ** 28)) 2) > > compute cobol-bit = function mod > > (function integer (member-id / (2 ** 26)) 2) > > compute amode = function mod > > (function integer (env-info / (2 ** 17)) 4) > > compute product-number = function integer > > (gpid / (2 ** 24)) > > compute version = function mod > > (function integer (gpid / (2 ** 16)) 256) > > compute releasse = function mod > > (function integer (gpid / (2 ** 8)) 256) > > compute modification = function mod > > (gpid 256) > > ----- > > > > > > > >
From: William M. Klein on 11 Mar 2007 06:53 You may be right (but I am still not certain) for IBM mainframes. According to: http://publibz.boulder.ibm.com/cgi-bin/bookmgr_OS390/BOOKS/igy3pg32/2.4.54 "TRUNC(STD) applies only to USAGE BINARY receiving fields in MOVE statements and arithmetic expressions." but it then goes on to say, "When TRUNC(STD) is in effect, the final result of an arithmetic expression, ...., is truncated" So I am not certain where in your compute statement the truncation would occur (if at all), i.e. for the "arithmetic expression" (evaluation) or in the FINAL move to the receiving field. I don't (easily) have an Enterprise COBOL system to test with, so I can't tell for sure. (I just "in general" HATE to rely on any stage of USAGE BINARY items where the data is larger than the PICTURE). P.S. If you haven't ever seen exactly what IBM does (and it IS different from Micro Focus), you might want to look at the examples at: http://publibz.boulder.ibm.com/cgi-bin/bookmgr_OS390/BOOKS/igy3pg32/2.4.54.1 and http://publibz.boulder.ibm.com/cgi-bin/bookmgr_OS390/BOOKS/igy3pg32/2.4.54.2 some of the results are truly "mind boggling" -- Bill Klein wmklein <at> ix.netcom.com "Rick Smith" <ricksmith(a)mfi.net> wrote in message news:12v7j5rd1ec59cd(a)corp.supernews.com... > > "William M. Klein" <wmklein(a)nospam.netcom.com> wrote in message > news:MsLIh.6139$pj4.2291(a)fe09.news.easynews.com... >> Richard, >> Are you assuming that "Moded fields" are USAGE BINARY-CHAR - or a > "BINARY" >> (with non-ANSI "notrunc" behavior). Otherwise, I don't know how you are >> processing them. This is part of my problem in "solving" this problem. >> Standard COBOL (pre- USAGE BINARY-CHAR) has no way to define a numeric > field as >> "binary" without truncation. > > PIC 9(9) BINARY > > The call to CEE3INF, as I understand it, will return the > values untruncated. Since truncation occurs when the > COBOL program stores the result of a calculation, I > don't see truncation, from the COMPUTE statements, > as a problem. > > The worrisome case appears to be getting bit 0 of a field, > such as, the CICS bit from sys/subsys; since this would > involve division by +2147483648 (2 ** 31). > > compute cics-bit = function mod > (function integer (sys-subsys / (2 ** 31)) 2) > > This statement correctly returns either +1 or +0 with > ANSI truncation (the default) in effect, on Micro Focus > COBOL 3.2.24. > > ----- > $set ibmcomp vsc2 arithmetic"vsc2" > identification division. > program-id. test3inf. > working-storage section. > 01 sys-subsys pic 9(9) binary value 0. > 01 cics-bit pic s9(4) binary value +0. > procedure division. > begin. > move x"80000000" to sys-subsys (1:4) > compute cics-bit = function mod > (function integer (sys-subsys / (2 ** 31)) 2) > if cics-bit = +1 > display "CICS bit is on" > end-if > goback. > ----- > >> "Rick Smith" <ricksmith(a)mfi.net> wrote in message >> news:12v6pek1atd1a64(a)corp.supernews.com... >> > >> > "William M. Klein" <wmklein(a)nospam.netcom.com> wrote in message >> > news:rrDIh.242220$k82.140284(a)fe07.news.easynews.com... >> >> to: comp.lang.cobol *and* IBM-MAIN >> >> >> >> IBM has (relatively) recently created an LE callable service, CEE3INF, >> > that >> >> returns a "32-bit map" with information about what environment a > program >> > is >> >> running in. See: >> >> >> >> >> > > http://publibz.boulder.ibm.com/cgi-bin/bookmgr_OS390/BOOKS/CEEA3170/2.2.5.9 >> >> >> >> Now, my question is how various "experienced" COBOL programmers would >> > handle >> >> such information (either in an IBM mainframe environment OR in other > COBOL >> >> environments for those who see this note and don't work in IBM > mainframe >> >> environments - but do get "bit maps") >> >> >> >> 1) Call a non-COBOL program to decode this map (e.g.. Assembler, C, > PL/I >> > or any >> >> other language that can easily handle "bits") >> >> >> >> 2) Do a "division" loop to figure out which bits are turned on? >> >> >> >> 3) Use 88-levels with hex literals to check for which bits were turned > on? >> >> >> >> 4) Use the LE (or comparable) "bit manipulation" routines? >> >> >> >> 5) Not use CEE3INF from COBOL? >> >> >> >> 6) Other? >> >> >> >> *** >> >> >> >> Although I wouldn't LIKE it, I can imagine doing this in any of these >> > ways. >> >> Obviously, when/if a COBOL compiler supports the '02 Standard > Bit/Boolean >> >> features, this becomes "trivial". However, as few (if any) compilers > do >> > this >> >> yet, I was wondering how programmers would handle this requirement. >> > >> > There are a lot of "reserved" bits in the four full-words. >> > While some of these may become assigned, it seems >> > unlikely that any would be moved. As new bits become >> > assigned, a routine that processes all bits, such as a >> > "division loop" would, I believe, be more sensitive to >> > maintenance than one that extracts the bit fields directly. >> > Also one need not extract more than is desired. >> > >> > Extracting these bit fields directly seems a rather >> > straight-forward process with intrinsic functions. The >> > exponents below are 31 minus the low-order bit number >> > of the field. >> > >> > ----- >> > compute c-bit = function mod >> > (function integer (member-id / (2 ** 28)) 2) >> > compute cobol-bit = function mod >> > (function integer (member-id / (2 ** 26)) 2) >> > compute amode = function mod >> > (function integer (env-info / (2 ** 17)) 4) >> > compute product-number = function integer >> > (gpid / (2 ** 24)) >> > compute version = function mod >> > (function integer (gpid / (2 ** 16)) 256) >> > compute releasse = function mod >> > (function integer (gpid / (2 ** 8)) 256) >> > compute modification = function mod >> > (gpid 256) >> > ----- >> > >> > >> > >> >> > >
From: Michael Mattias on 11 Mar 2007 10:12 01 SYS-SUSBSYS PIC S9(09) USAGE BINARY CALL 'CEE3INF' USING BY REFERENCE SYS-SUBYS ..... DIVIDE SYS-SUBSYS BY 2 GIVING X REMAINDER BIT-0 (You can just 'ladder' DIVIDE by 2 and keeping remainders; the remainders will be the bits) MCM
From: Pete Dashwood on 11 Mar 2007 20:50 "William M. Klein" <wmklein(a)nospam.netcom.com> wrote in message news:rrDIh.242220$k82.140284(a)fe07.news.easynews.com... > to: comp.lang.cobol *and* IBM-MAIN > > IBM has (relatively) recently created an LE callable service, CEE3INF, > that returns a "32-bit map" with information about what environment a > program is running in. See: > > http://publibz.boulder.ibm.com/cgi-bin/bookmgr_OS390/BOOKS/CEEA3170/2.2.5.9 I had a bit of spare time after a heavy weekend so I checked your link above and then downloaded the z/OS COBOL manual to see what you can actually DO... I note with regret that PIC 1 (Binary) is missing... :-) (Now, THAT's something that would be much more useful in the COBOL standard than embedded XML...) Anyway, having faced this problem in the Client/Server environment some years back I am satisifed that the problem is NOT about what bits mean what, it is about being able to reference bits from COBOL at all. You mentioned the traditional approaches and I've given my opinions below. > > Now, my question is how various "experienced" COBOL programmers would > handle such information (either in an IBM mainframe environment OR in > other COBOL environments for those who see this note and don't work in IBM > mainframe environments - but do get "bit maps") > > 1) Call a non-COBOL program to decode this map (e.g.. Assembler, C, PL/I > or any other language that can easily handle "bits") No. I looked at doing it in Java and then invoking the Java class from z/OS but it would have taken more time than I was prepared to spend on it to fully investigate and code the solution.(If I was working in a mainframe environment, I'd simply invest the time and do it this way. Java is fully transportable and so should COBOL be, if that is important to you. (It is a consideration for me, but not a show stopper...) This approach has the advantages that it is OO, encapsulated, and transportable. > > 2) Do a "division" loop to figure out which bits are turned on? Yeah, brute force. Effective but inelegant. > > 3) Use 88-levels with hex literals to check for which bits were turned on? Imaginative, but a bit ugly. > > 4) Use the LE (or comparable) "bit manipulation" routines? Certainly that was the approach I opted for in the MicroFocus environment many years ago. They provided bit conversion routines that were callable from COBOL, but of course, as soon as you use them, any hope of platform transportability is gone... > > 5) Not use CEE3INF from COBOL? > Seems a bit drastic :-) > 6) Other? > Given that the real problem is converting bits to bytes so COBOL can address them, it seemed to me that the Java option is the one I would go for. However, I then read Rick's post and it is simple and elegant. I understand you have some reservations about it working with mainframe TRUNC options but I'd simply try it out as quickly as possible. Given that it worked, I'd go with that. The intrinsic MOD function it uses is available on every platform I've seen that supports intrinsic functions... I reckon this is imagnative simple and direct. Definitely gets my vote. Pete.
From: Pete Dashwood on 11 Mar 2007 20:51 "Rick Smith" <ricksmith(a)mfi.net> wrote in message news:12v6pek1atd1a64(a)corp.supernews.com... > > "William M. Klein" <wmklein(a)nospam.netcom.com> wrote in message > news:rrDIh.242220$k82.140284(a)fe07.news.easynews.com... >> to: comp.lang.cobol *and* IBM-MAIN >> >> IBM has (relatively) recently created an LE callable service, CEE3INF, > that >> returns a "32-bit map" with information about what environment a program > is >> running in. See: >> >> > http://publibz.boulder.ibm.com/cgi-bin/bookmgr_OS390/BOOKS/CEEA3170/2.2.5.9 >> >> Now, my question is how various "experienced" COBOL programmers would > handle >> such information (either in an IBM mainframe environment OR in other >> COBOL >> environments for those who see this note and don't work in IBM mainframe >> environments - but do get "bit maps") >> >> 1) Call a non-COBOL program to decode this map (e.g.. Assembler, C, PL/I > or any >> other language that can easily handle "bits") >> >> 2) Do a "division" loop to figure out which bits are turned on? >> >> 3) Use 88-levels with hex literals to check for which bits were turned >> on? >> >> 4) Use the LE (or comparable) "bit manipulation" routines? >> >> 5) Not use CEE3INF from COBOL? >> >> 6) Other? >> >> *** >> >> Although I wouldn't LIKE it, I can imagine doing this in any of these > ways. >> Obviously, when/if a COBOL compiler supports the '02 Standard Bit/Boolean >> features, this becomes "trivial". However, as few (if any) compilers do > this >> yet, I was wondering how programmers would handle this requirement. > > There are a lot of "reserved" bits in the four full-words. > While some of these may become assigned, it seems > unlikely that any would be moved. As new bits become > assigned, a routine that processes all bits, such as a > "division loop" would, I believe, be more sensitive to > maintenance than one that extracts the bit fields directly. > Also one need not extract more than is desired. > > Extracting these bit fields directly seems a rather > straight-forward process with intrinsic functions. The > exponents below are 31 minus the low-order bit number > of the field. > > ----- > compute c-bit = function mod > (function integer (member-id / (2 ** 28)) 2) > compute cobol-bit = function mod > (function integer (member-id / (2 ** 26)) 2) > compute amode = function mod > (function integer (env-info / (2 ** 17)) 4) > compute product-number = function integer > (gpid / (2 ** 24)) > compute version = function mod > (function integer (gpid / (2 ** 16)) 256) > compute releasse = function mod > (function integer (gpid / (2 ** 8)) 256) > compute modification = function mod > (gpid 256) > ----- > > > Excellent! Great stuff, Rick. Pete.
First
|
Prev
|
Next
|
Last
Pages: 1 2 3 4 5 Prev: Cobol convert program Job Request Next: Conversion of data & associated logic from ISAM to RDB |