Month: May 2020

Does this COBOL level-88 IF check make any sense?

May 21, 2020 COBOL ,

I find COBOL level-88 declarations a bit confusing, which isn’t made any easier by usage that is probably wrong. Here’s an example from code that I was trying to step through in the debugger (anonymized):

       WORKING-STORAGE SECTION.
       01  data.
           10  function-type         PIC  X(01).
               88  option-a          VALUE '1'.
               88  option-b          VALUE '2'.
               88  option-c          VALUE '3'.
               88  option-d          VALUE '4'.

With the use like so:

           IF option-a AND option-b AND option-c
           NEXT SENTENCE ELSE GO TO meaningless-label-2.

It’s my understanding that this is essentially equivalent to:

           IF function-type = '1' AND function-type = '2' AND
              function-type = '3'
           NEXT SENTENCE ELSE GO TO meaningless-label-2.

Do I misunderstand the level-88 variables should be used, or is this just a plain old impossible-to-be-true if check? Putting this into a little sample program, confirms that we hit the ELSE:

       IDENTIFICATION DIVISION.
       PROGRAM-ID.                 TESTPROG.
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01  data.
           10  function-type         PIC  X(01).
               88  option-a          VALUE '1'.
               88  option-b          VALUE '2'.
               88  option-c          VALUE '3'.
               88  option-d          VALUE '4'.
       PROCEDURE DIVISION.
           move '1' to function-type

           perform meaningless-label-1 thru meaningless-label-6

           goback
           .

       meaningless-label-1.

      *    IF function-type = '1' AND function-type = '2' AND
      *       function-type = '3'
           IF option-a AND option-b AND option-c
           NEXT SENTENCE ELSE GO TO meaningless-label-2.

           display 'IF was true.'

           goto meaningless-label-6
           .

       meaningless-label-2.

           display 'IF was not true.'
           .

       meaningless-label-6.
           EXIT
           .

I get SYSOUT of:

IF was not true.

as I expected. If these were level-88 variables each “belonging” to a different variable, such as:

       IDENTIFICATION DIVISION.
       PROGRAM-ID.                 TESTPROG.
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01  data.
           10  blah                 PIC  X(01).
               88  blah-option-a                 VALUE '1'.
               88  blah-option-b                 VALUE '2'.
           10  foo                  PIC  X(01).
               88  foo-option-a                  VALUE '1'.
               88  foo-option-b                  VALUE '2'.
               88  foo-option-c                  VALUE '3'.
           10  bar                  PIC  X(01).
               88  bar-option-c                  VALUE '3'.
               88  bar-option-d                  VALUE '4'.

       PROCEDURE DIVISION.
           move '1' to blah
           move '2' to foo
           move '3' to bar

           perform meaningless-label-1 thru meaningless-label-6

           goback
           .

       meaningless-label-1.

           IF blah-option-a AND foo-option-b AND bar-option-c
           NEXT SENTENCE ELSE GO TO meaningless-label-2.

           display 'IF was true.'

           goto meaningless-label-6
           .

       meaningless-label-2.

           display 'IF was not true.'
           .

       meaningless-label-6.
           EXIT
           .

This has the ‘IF was true’ SYSOUT. Perhaps the original coder meant to use OR instead of AND?

COBOL spaghetti code: EXIT does nothing!

May 20, 2020 COBOL , , , , , , , , , ,

I was staring down COBOL code of the following form:

       LOOP-COUNTER-INCREMENT.
           ADD 1 TO J.
       LOOP-PREDICATE-CHECK.   
           IF J GREATER 10 GO TO MYSTERIOUS-LABEL-1.
           
           IF ARRAY-1 (J)      NOT = ZERO
           NEXT SENTENCE ELSE GO TO MYSTERIOUS-LABEL-1.
           
           IF ARRAY-2 (J) = MYSTERIOUS-MAGIC-NUMBER-CONSTANT
           NEXT SENTENCE ELSE GO TO COUNTER-INCREMENT-SPAGGETTIFI.
           
     *     ...MORE STUFF...                                        
     
           GO TO MYSTERIOUS-LABEL-3.
           
       COUNTER-INCREMENT-SPAGGETTIFI.
           GO TO LOOP-COUNTER-INCREMENT.
           
       MYSTERIOUS-LABEL-1.
                       EXIT.
       MYSTERIOUS-LABEL-2.
                       EXIT.
       MYSTERIOUS-LABEL-3.
                       EXIT.

I had to get some guru help understanding what this was about (thanks Roger!). I didn’t understand why somebody would code a GOTO LABEL, when the the code at that LABEL just did an EXIT. If my intuition could be trusted, I would have assumed that this code was equivalent to the much simpler:

       LOOP-COUNTER-INCREMENT.
           ADD 1 TO J.
       LOOP-PREDICATE-CHECK.   
           IF J GREATER 10 EXIT.
           
           IF ARRAY-1 (J)      NOT = ZERO
           NEXT SENTENCE ELSE EXIT.
           
           IF ARRAY-2 (J) = MYSTERIOUS-MAGIC-NUMBER-CONSTANT
           NEXT SENTENCE ELSE GO TO LOOP-COUNTER-INCREMENT.
           
     *     ...MORE STUFF...                                        
     
           EXIT.

It turns out that intuition is not much use when looking at COBOL code. In this case, that intuition failure is because EXIT doesn’t actually do anything. It is not like a return, which is what I assumed, but is just something that you can put in a paragraph at the end of the section so that the code can exit the section (or at the end of a sequence of paragraphs invoked by PERFORM THRU, so that the code can return to the caller.)  The EXIT in such a paragraph is just a comment, and you could use an empty paragraph to do the same thing.

In my transformation of the code the EXIT would do nothing, and execution would just fall through to the next sentence!

Some of the transformations I made are valid. In particular, the spaghettification-indirection used to increment the loop counter, by using a goto to goto the target location instead of straight there, has no reason to exist.

The code in question was an edited version of a program that was generated by a 4GL language (DELTA), so some of the apparent stupidity can be blamed on the code generator. I also assume DELTA can also be blamed for the multiple EXIT paragraphs, when it would seem more natural to just have one per section.

This code also uses EXIT after other paragraph labels too. The first paragraph in the following serving of horror has such an example:

            PERFORM TRANSFER-CHECK THRU TRANSFER-CHECK-EXIT.

            [snip]

       TRANSFER-CHECK.
                       EXIT.
       MEANINGLESS-LABEL-1.
           IF [A COMPOUND PREDICATE CHECK]
           NEXT SENTENCE ELSE GO TO MEANINGLESS-LABEL-2.
                 [SNIP]
           PERFORM [MORE STUFF]
           GO TO MEANINGLESS-LABEL-100.
       MEANINGLESS-LABEL-2.
           [STUFF]
           GO TO MEANINGLESS-LABEL-4.
       MEANINGLESS-LABEL-3.
           [increment loop counter, and fall through]
       MEANINGLESS-LABEL-4.
           [loop body]
...
       MEANINGLESS-LABEL-50.
           GO TO MEANINGLESS-LABEL-3.
           [SNIP]
...
       MEANINGLESS-LABEL-99.                            
                       EXIT.                               
       MEANINGLESS-LABEL-100.                                       
                       EXIT. 
       TRANSFER-CHECK-EXIT.
                       EXIT.

Nothing ever branches to MEANINGLESS-LABEL-1 directly, so why even have that there? Using my new found knowledge that EXIT doesn’t do anything, I’m pretty sure that you could just write:

            PERFORM TRANSFER-CHECK THRU TRANSFER-CHECK-EXIT.

            [snip]

       TRANSFER-CHECK.
       
           IF [A COMPOUND PREDICATE CHECK]

Is there some subtle reason that this first no-op paragraph was added? My guess is that the programmer was either being paid per line of code, or the code generator is to blame.

I’m not certain about the flow-control in the TRUE evaluation above. My intuition about the THRU use above is that if we have a GOTO that bypasses one of the paragraphs, then all the preceding paragraphs are counted as taken (i.e. if you get to the final paragraph in the THRU evaluation, no matter how you get there, then you are done.) I’ll have to do an experiment to determine if that’s actually the case.

My old Quantum II notes are now available on amazon

May 17, 2020 phy456 , , , , , , , , ,

PHY456, Quantum Mechanics II was one of the first few courses that I did as part of my non-degree upper year physics program.  That was a self directed study part time program, where I took most of interesting seeming fourth year undergrad physics courses at UofT.

I was never really pleased with how my QMII notes came out, and unlike some of my other notes compilations, I never made a version available on amazon, instead just had the PDF available for free on my Quantum Mechanics page.  That page also outlines how to get a copy of the latex sources for the notes (for the curious, or for the zealous reader who wants to submit merge requests with corrections.)

Well, over the last month or so, I’ve gradually cleaned up these QMII notes enough that they are “print-ready” (no equations overflowing into the “gutter”, …) , and have gone ahead and made it available on amazon, for $10 USD.  Like my other class notes “books”, this is published using amazon’s print on demand service.  In the likely event that nobody will order a copy, there is no upfront requirement for me to order a minimal sized print run, and then be stuck with a whole bunch of copies that I can’t give away.

There are still lots of defects in this set of notes.  In particular, I seem to have never written up my problem set solutions in latex, and subsequently lost those solutions.  There’s also lots of redundant material, as I reworked a few of the derivations multiple times, and never went back and purged the crud.  That said, they are available as-is, now in paper form, as well as a free PDF.

I’ll share the preface, and the contents below.

Preface.

These are my personal lecture notes for the Fall 2011, University of Toronto Quantum mechanics II course (PHY456H1F), taught by Prof. John E Sipe.

The official description of this course was:

“Quantum dynamics in Heisenberg and Schrodinger Pictures; WKB approximation; Variational Method; Time-Independent Perturbation Theory; Spin; Addition of Angular Momentum; Time-Dependent Perturbation Theory; Scattering.”

This document contains a few things

  • My lecture notes.
  • Notes from reading of the text \citep{desai2009quantum}. This may include observations, notes on what seem like errors, and some solved problems.
  • Different ways of tackling some of the assigned problems than the solution sets.
  • Some personal notes exploring details that were not clear to me from the lectures.
  • Some worked problems.

There were three main themes in this course, my notes for which can be found in

  • Approximate methods and perturbation,
  • Spin, angular momentum, and two particle systems, and
  • Scattering theory.

Unlike some of my other course notes compilations, this one is short and contains few worked problems. It appears that I did most of my problem sets on paper and subsequently lost my solutions. There are also some major defects in these notes:

  • There are plenty of places where things weren’t clear, and there are still comments to followup on those issues to understand them.
  • There is redundant content, from back to back lectures on materials that included review of the previous lecture notes.
  • A lot of the stuff in the appendix (mostly personal notes and musings) should be merged into the appropriate lecture note chapters. Some work along those lines has been started, but that work was very preliminary.
  • I reworked some ideas from the original lecture notes to make sense of them (in particular, adiabatic approximation theory), but then didn’t go back and consolidate all the different notes for the topic into a single coherent unit.
  • There were Mathematica notebooks for some of the topics with issues that I never did figure out.
  • Lots of typos, bad spelling, and horrendous grammar.
  • The indexing is very spotty.

Hopefully, despite these and other defects, these notes may be of some value to other students of Quantum Mechanics.

I’d like to thank Professor Sipe for teaching this course. I learned a lot and it provided a great foundation for additional study.

Phy456 (QM II) Contents:

  • Copyright
  • Document Version
  • Dedication
  • Preface
  • Contents
  • List of Figures
  • 1 Approximate methods.
  • 1.1 Approximate methods for finding energy eigenvalues and eigenkets.
  • 1.2 Variational principle.
  • 2 Perturbation methods.
  • 2.1 States and wave functions.
  • 2.2 Excited states.
  • 2.3 Problems.
  • 3 Time independent perturbation.
  • 3.1 Time independent perturbation.
  • 3.2 Issues concerning degeneracy.
  • 3.3 Examples.
  • 4 Time dependent perturbation.
  • 4.1 Review of dynamics.
  • 4.2 Interaction picture.
  • 4.3 Justifying the Taylor expansion above (not class notes).
  • 4.4 Recap: Interaction picture.
  • 4.5 Time dependent perturbation theory.
  • 4.6 Perturbation expansion.
  • 4.7 Time dependent perturbation.
  • 4.8 Sudden perturbations.
  • 4.9 Adiabatic perturbations.
  • 4.10 Adiabatic perturbation theory (cont.)
  • 4.11 Examples.
  • 5 Fermi’s golden rule.
  • 5.1 Recap. Where we got to on Fermi’s golden rule.
  • 5.2 Fermi’s Golden rule.
  • 5.3 Problems.
  • 6 WKB Method.
  • 6.1 WKB (Wentzel-Kramers-Brillouin) Method.
  • 6.2 Turning points..
  • 6.3 Examples.
  • 7 Composite systems.
  • 7.1 Hilbert Spaces.
  • 7.2 Operators.
  • 7.3 Generalizations.
  • 7.4 Recalling the Stern-Gerlach system from PHY354.
  • 8 Spin and Spinors.
  • 8.1 Generators.
  • 8.2 Generalizations.
  • 8.3 Multiple wavefunction spaces.
  • 9 Two state kets and Pauli matrices.
  • 9.1 Representation of kets.
  • 9.2 Representation of two state kets.
  • 9.3 Pauli spin matrices.
  • 10 Rotation operator in spin space.
  • 10.1 Formal Taylor series expansion.
  • 10.2 Spin dynamics.
  • 10.3 The hydrogen atom with spin.
  • 11 Two spins, angular momentum, and Clebsch-Gordon.
  • 11.1 Two spins.
  • 11.2 More on two spin systems.
  • 11.3 Recap: table of two spin angular momenta.
  • 11.4 Tensor operators.
  • 12 Rotations of operators and spherical tensors.
  • 12.1 Setup.
  • 12.2 Infinitesimal rotations.
  • 12.3 A problem.
  • 12.4 How do we extract these buried simplicities?
  • 12.5 Motivating spherical tensors.
  • 12.6 Spherical tensors (cont.)
  • 13 Scattering theory.
  • 13.1 Setup.
  • 13.2 1D QM scattering. No potential wave packet time evolution.
  • 13.3 A Gaussian wave packet.
  • 13.4 With a potential.
  • 13.5 Considering the time independent case temporarily.
  • 13.6 Recap.
  • 14 3D Scattering.
  • 14.1 Setup.
  • 14.2 Seeking a post scattering solution away from the potential.
  • 14.3 The radial equation and its solution.
  • 14.4 Limits of spherical Bessel and Neumann functions.
  • 14.5 Back to our problem.
  • 14.6 Scattering geometry and nomenclature.
  • 14.7 Appendix.
  • 14.8 Verifying the solution to the spherical Bessel equation.
  • 14.9 Scattering cross sections.
  • 15 Born approximation.
  • A Harmonic oscillator Review.
  • A.1 Problems.
  • B Simple entanglement example.
  • C Problem set 4, problem 2 notes.
  • D Adiabatic perturbation revisited.
  • E 2nd order adiabatically Hamiltonian.
  • F Degeneracy and diagonalization.
  • F.1 Motivation.
  • F.2 A four state Hamiltonian.
  • F.3 Generalizing slightly.
  • G Review of approximation results.
  • G.1 Motivation.
  • G.2 Variational method.
  • G.3 Time independent perturbation.
  • G.4 Degeneracy.
  • G.5 Interaction picture.
  • G.6 Time dependent perturbation.
  • G.7 Sudden perturbations.
  • G.8 Adiabatic perturbations.
  • G.9 WKB.
  • H Clebsh-Gordan zero coefficients.
  • H.1 Motivation.
  • H.2 Recap on notation.
  • H.3 The \(J_z\) action.
  • I One more adiabatic perturbation derivation.
  • I.1 Motivation.
  • I.2 Build up.
  • I.3 Adiabatic case.
  • I.4 Summary.
  • J Time dependent perturbation revisited.
  • K Second form of adiabatic approximation.
  • L Verifying the Helmholtz Green’s function.
  • M Mathematica notebooks.
  • Index
  • Bibliography

Reverse engineering a horrible COBOL structure initialization

May 16, 2020 Mainframe , , , ,

The COBOL code that I was looking at used a magic value 999, and I couldn’t see where it could be coming from.  After considerable head scratching, I managed to figure out that all the array structure instantiations in the code are initialized using strings.  That seems to be the origin of the magic (standalone) 999’s scattered through the code.

To share the horror, here is an (anonymized) example of the offending array structure initialization

where I added in the block comment that points out each of the interesting regions of the initialization strings.

Here’s what’s going on.  We have a global variable array (effectively unnamed) that has three fields:

  • two-characters (numeric only)
  • dummy-structure-name, containing a 3 character field and a pad.
  • nine-more-characters

If you add up all the characters in this data structure we have: 2 + 1 + 4 * (3 + 1) + 9 = 28, so this array initialization is effectively done by aliasing the array elements with the memory containing a char[7][28].

My eyes are burning!

As far as I can tell, COBOL has no notion of a structure type, you just have instances of structures everywhere (they are probably called something different — a level 01 declaration, or something like that).  A lot of the PL/I code I’ve seen is also like that, although in PL/I you can declare your structure types if you want to.

The display’s above make use of the fact that COBOL variables don’t have to use all the high level qualifiers (unless there is ambiguity).  My SYSOUT shows that, sure enough, the (5) element of the array (COBOL arrays are one’s counted) has the values I expected:

1 22
2 999
3 1/2
4
5
6 SF

Basically, the horrendous initialization above, is as if you if declared your structure as:

struct arrayname
{                   
   char numeric2[2];
   char filler1[1];
   struct               
   {                 
      char threemore[3];
      char filler2[1];
   } threepluspad[4];

   char ninemore[9];     
}; 

and then initialized it with:

char globalmemory[7][28] = {
   // n2       f    x    x    x    y    x    x    x    y    x    x    x    y    x    x    x    y    'K', 'l', 'a', 's', 's', 'e', ' ', ' ', ' '},
   { '0', '1', ' ', ' ', ' ', '0', ' ', ' ', ' ', '0', ' ', ' ', ' ', ' ', ' ', ' ', ' ', ' ', ' ', 'K', 'l', 'a', 's', 's', 'e', ' ', ' ', ' '},
   { '0', '2', ' ', ' ', ' ', '0', ' ', ' ', ' ', '0', ' ', ' ', ' ', ' ', ' ', ' ', ' ', ' ', ' ', 'K', 'l', 'a', 's', 's', 'e', ' ', ' ', ' '},
   { '1', '3', ' ', '9', '9', '9', ' ', '9', '9', '9', ' ', ' ', ' ', ' ', ' ', ' ', ' ', ' ', ' ', 'K', 'l', 'a', 's', 's', 'e', ' ', ' ', ' '},
   { '2', '1', ' ', '9', '9', '9', ' ', '1', '/', '2', ' ', ' ', ' ', ' ', ' ', ' ', ' ', ' ', ' ', 'S', 'F', ' ', ' ', ' ', ' ', ' ', ' ', ' '},
   { '2', '2', ' ', '9', '9', '9', ' ', '1', '/', '2', ' ', ' ', ' ', ' ', ' ', ' ', ' ', ' ', ' ', 'S', 'F', ' ', ' ', ' ', ' ', ' ', ' ', ' '},
   { '2', '3', ' ', '1', '/', '2', ' ', '1', '/', '2', ' ', ' ', ' ', ' ', ' ', ' ', ' ', ' ', ' ', 'S', 'F', ' ', ' ', ' ', ' ', ' ', ' ', ' '},
   { '3', '1', ' ', ' ', ' ', '1', ' ', ' ', ' ', '1', ' ', ' ', ' ', ' ', ' ', ' ', ' ', ' ', ' ', 'S', 'F', ' ', ' ', ' ', ' ', ' ', ' ', ' '},
};

struct arrayname * p = (struct arrayname*)globalmemory;

and then and then printed:

   printf( "1 %.2s\n", p[4].numeric2 );
   printf( "2 %.3s\n", p[4].threepluspad[0].threemore );
   printf( "3 %.3s\n", p[4].threepluspad[1].threemore );
   printf( "4 %.3s\n", p[4].threepluspad[2].threemore );
   printf( "5 %.3s\n", p[4].threepluspad[3].threemore );
   printf( "6 %.9s\n", p[4].ninemore );

Of course, the use of fixed length strings without a null terminator wouldn’t ever be done in C, so a more natural equivalent (assuming one doesn’t care about the specific memory equivalence of the two representations, and can tolerate null terminators instead of spaces) would just be something like:

struct arrayname
{
   char numeric2[3];
   struct 
   {
      char threemore[4];
   } threepluspad[4];

   char ninemore[9];
};

struct arrayname g[7] = {
   { "01", {"  0", "  0", "   ", "   "}, "Klasse  " },
   { "02", {"  0", "  0", "   ", "   "}, "Klasse  " },
   { "13", {"999", "999", "   ", "   "}, "Klasse  " },
   { "21", {"999", "1/2", "   ", "   "}, "SF      " },
   { "22", {"999", "1/2", "   ", "   "}, "SF      " },
   { "23", {"1/2", "1/2", "   ", "   "}, "SF      " },
   { "31", {"  1", "  1", "   ", "   "}, "SF      " }
};  

You could argue that the COBOL way isn’t so bad once you’ve seen the pattern, and is only cosmetically different from the natural C analogue. That is, if you ignore the fact that there is no separation of fields in the initializer strings, and that you have to name a whole bunch of dummy initializer objects and fill characters, and the fact that any semblance of typing is completely obliterated.

The code in question is also complete spaghetti, with GOTO all over the place.  Perhaps COBOL versions after COBOL77, which is what I assume I’m looking at, added loops and better initialization syntax?

Computing “offsetof” in COBOL

May 15, 2020 Mainframe , , , , ,

I couldn’t find a way to compute something like C offsetof in COBOL code.  What I could manage to figure out how to do is compare addresses of a runtime instantiation of the structure, effectively doing this indirectly.  Here’s the ugly mess that I cooked up:

I couldn’t figure out the right syntax to do a single compute statement that was just the difference of addresses, as I got numeric/pointer compare errors from the compiler, no matter what I tried.  I think that ‘USAGE IS POINTER’ may be required on my variables, but that would still require a temporary.  I’m probably either doing this the hard way, or there is no easy way in COBOL.

This program was run with the following simple JCL

//TESTPROG JOB
//A EXEC PGM=TESTPROG
//SYSOUT DD SYSOUT=*
//STEPLIB DD DSN=COBRC.NATIVE.TESTPROG,
// DISP=SHR

and produced the following SYSOUT

address of TESTPROG-STRUCT = 0016800264
offsetof(ARRAY-NAME,RUECK-BKL) = 0000000002
offsetof(ARRAY-NAME,RUECK-BS) = 0000000004
offsetof(ARRAY-NAME,RUECK-SF) = 0000000007
sizeof(ARRAY-NAME(1)) = 0000000019

Looking at that output, we can conclude the following:

  • PIC S9(3) COMP-3 is effectively horrible eye-burning syntax for a “short”
  • There is no alignment padding between fields, nor end of array-member padding to force natural alignment of the next array element, should the structure start have been aligned.

I knew the latter, but wasn’t sure what size the first field was, and thought that trying to figure it out with COBOL code would be a good learning exercise.