Click here to Skip to main content
15,889,034 members
Articles / Operating Systems / Windows

Enforced Type Safety Using Generics In COBOL

Rate me:
Please Sign up or sign in to vote.
0.00/5 (No votes)
2 Feb 2010CC (ASA 2.5)7 min read 11.7K   2  
Using the latest versions of COBOL, this venerable language becomes completely type safe via generics - shown by example.

Abstract

Generics can guarantee absolute type safety at compile time which has massive benefits for bug free code. Here I shall discuss some of the ideas in this area when working in Managed COBOL.

Please Note

Please note that this post uses COBOL syntax which will not be available as general release until the next version of Micro Focus managed COBOL as of the time of writing (Feb 2010). However, the principles of generic programming are transferable to previous versions of COBOL and other languages.

Introduction

In old style COBOL, we can move anything to anything; there is precious little type safety of any kind and it is up to the programmer to avoid doing stuff which will cause the program to produce incorrect results or just plain crash.

* Here is an example of absolute type blindness.
* This program is about as safe as putting
* a black mamba down your trousers and sounding
* a fog horn whilst dancing the tango.
 data division.
 working-storage section.
 01 my-group.
    03 thing1 pic s9(5)v9(5).
    03 thing2 pic x(10).
 linkage section.
 01 x pic x.
 procedure division.
     move 12345.12345          to thing1
     move "dog day afternoons" to thing2
     call "dangerous" using my-group
     goback.

     entry "dangerous" using  x

     display x(1:20)
     goback.

Please do not get me wrong here; I am not saying that non type safe code is actually bad code. It is a coding style with advantages and disadvantages. It is my personal experience that projects move forward faster when code is written type safe. The reason for this is that such projects get less of those 'why the goodness is this not working!' moments. All those moments add up to occupy more developer time than the actual coding itself. The more type safe coding gets, the faster it seems to get written. The same applies double for code maintenance where the maintainer does not have the same intimate knowledge of the program structure that the originator did.

OK, with that all said, what can we do about type safety? I could now launch into a long discussion of object orientation and how one can use super classes and casts to improve type safety. But why would I do that when it is not 100% type safe? Such approaches are nice and give us a warm feeling inside but... absolute, complete and utter type safety – that is what we really want (well I do). I want to nail it, splat it and stomp unsafe typing to bits. I don't ever want to see a cast exception ever again. So I am going to go straight for the state of the art (in imperative programming at least).

Generic Programming – Finally Problem Solved!

  1. If you have to cast – you've failed!
  2. X as type Y is so bad you should hang your head in shame and cry at your pathetic nature!

Hold these mantras to your heart and you shall reign supreme as a generics programmer! Yes – it will take some re-learning and probably some head aches if you are not new to the idea of object orientation (my experience is that people who are new to the idea actually find it easier to pick up generics). Never mind, let us just dive in and start swimming!

$set ilusing(System.Collections.Generic)
     method-id main static.
         01 my-float-list type List[float-long].

Nice - we now have a list of float-long elements. System.Collections.Generic.List is a generic class. When we use one of these, we must say what type it contains. In the above example, we cannot not do invoke my-float-list::Add(“Hello World”). The compiler records that the list my-float-list is a list of float-long and so rejects the type incorrect code. Note: The compiler does the rejection, not the runtime. This all happens before we run the program and converts any horrid “why does it not work” into the easy to figure out “why does it not compile” things! (I am not supposed to say problem – so I say thing...).

The Micro Focus managed COBOL compiler has a whole set of systems which track generics and their type (as does the Microsoft C# compiler for example). This eye wateringly clever piece of kit does all the hard work of enforcing type safety so that you do not have to.

Creating Our Own Generics

This post is not going to be a full chapter from a book which gives a detailed discussion on generic programming in managed COBOL; my approach is to take an example and work it through to completion and hope that gives enough ideas to get the idea across. My example is a notional application for doing three dimensional mathematics. Such a thing might be handy in a modelling tool or a 3D drawing package. The aim is to create this application in such a way that it is generically extensible to use any mathematical representation on which basic arithmetic can be performed. We do not want to have to worry about defining up front if it is using float-long, binary-double or some other mathematical type (later I will show an example using numbers stored in strings). We should not even have to know what mathematical type is to be used when we write the code. We want it to be … generic!

  • My demo application has to have something to represent the idea of a point in three dimensional space. I call this Point3D.
  • A Point3D will have to hold three things which can be treated as numbers. To achieve this, I have created a completely generic definition of a number. I call this IComputable. IComputable is a generic interface IComputable[T] where T is the generic type of the interface and represents the data type used to actually store the number.
  • Any class implementing IComputable[T] will have to implement the methods defined in IComputable for numbers stored in Type T.

Here is IComputable[T]:

interface-id IComputable using T.

    method-id #Add public.
        procedure division using by value
             toAdd as type IComputable[T]
             returning ret as type IComputable[T].
    end method.

    method-id #Subtract public.
        procedure division using by value
             toSubtract as type IComputable[T]
             returning ret as type IComputable[T].
    end method.

    method-id #Square public.
        procedure division returning ret as type IComputable[T].
    end method.

    method-id #Sqrt public.
        procedure division returning ret as type IComputable[T].
    end method.

    method-id GetValue public.
        procedure division returning ret as T.
    end method.

 end interface.

This simple interface defines methods for addition, subtraction, finding the square and the square route for numbers stored in type T. It also provides a method for getting at the number as stored via the GetValue method. The entire interface is 'parametrised' which means that it takes a parameter T which is the data type in which the number is stored. All the computational methods return an IComputable[T] and, where they have arguments, these are also of type IComputable[T]. The GetValue method as a return type of T itself. In this way, the interface is completely locked down, everything going in or out of it is locked to T or to something parametrised with T. We can see this as completing a circle – if everything going in and everything going out is parametrised by the same generic type, we get a type safe construct.

Next, let us look at my implementation of Point3D:

class-id Point3D using T.

    01 _x type IComputable[T].
    01 _y type IComputable[T].
    01 _z type IComputable[T].

    method-id get property x public.
        procedure division returning ret as type IComputable[T].
        move _x to ret
    end method.

    method-id get property y public.
        procedure division returning ret as type IComputable[T].
        move _y to ret
    end method.

    method-id get property z public.
        procedure division returning ret as type IComputable[T].
        move _z to ret
    end method.

    method-id GetDistance public static.
        01 inter type IComputable[T].
        procedure division
        using  by value
            startPoint as type Point3D[T]
            endPoint   as type Point3D[T]
        returning
            ret        as type IComputable[T].

            set inter to startPoint::x::Subtract(endPoint::x)::Square

            set inter to inter::Add
            (
                startPoint::y::Subtract(endPoint::y)::Square
            )

            set inter to inter::Add
            (
                startPoint::z::Subtract(endPoint::z)::Square
            )

            set ret to inter::Sqrt

    end method.

    *> The parameters of the new method link the type of IComputable to the
    *> type of the Point3D class and so fully enforce type safety
    method-id new public.

       procedure division
       using by value
            x-in as type IComputable[T]
            y-in as type IComputable[T]
            z-in as type IComputable[T].

           move x-in to self::_x
           move y-in to self::_y
           move z-in to self::_z
           goback
    end method.

end class.

Again, everything is parametrised with the same generic parameter. All the internal storage (_x, _y and _z) is of type IComputable[T] and all return types and arguments are of type IComputable[T]. We can think about what this means to the compiler. Note that the letter T is not important (it would be a non reserved word - DOG for instance). The key issue from the point of view of the compiler is that the same generic parameter is used throughout the class definition. This means that when we come to make a concrete version of the class, the same type gets used everywhere in the class where T is in the generic definition. That is a whole bunch of words, so here is what I mean in code:

*> We have a generic class fragment like this:
       class-id Point3D using T.

           01 _x type IComputable[T].
           01 _y type IComputable[T].
           01 _z type IComputable[T].

           method-id get property x public.
               procedure division returning ret as type IComputable[T].
               move _x to ret
           end method.

*> We can make a concrete Object from this like so:
        01 myPoint type Point3D[binary-long].

*> The compiler's internal representation for myPoint (is actually quite complex)
*> but can be thought of as being something like this:
       class-id Point3D using T.

           01 _x type IComputable[binary-long].
           01 _y type IComputable[binary-long].
           01 _z type IComputable[binary-long].

           method-id get property x public.
               procedure division returning ret as type IComputable[binary-long].
               move _x to ret
           end method.

*> If we make believe that there is a class with the name BigFloat then ...
        01 myPoint type Point3D[type BigFloat].

*> ... could be thought of as:
       class-id Point3D using T.

           01 _x type IComputable[type BigFloat].
           01 _y type IComputable[type BigFloat].
           01 _z type IComputable[type BigFloat].

           method-id get property x public.
               procedure division returning ret as type IComputable[type BigFloat].
               move _x to ret
           end method. 

Now I need to put together a real example of IComputable[T]. To do that, we can use 'parametrised implements':

class-id ComputableString implements type IComputable[string].

Here we have said that ComputableString will implement IComputable for type string. Thus ComputableString can be passed as an argument to anything taking IComputable[T] as long as T is string. Take the new method (the constructor) of my Point3D class:

method-id new public.

   procedure division
   using by value
        x-in as type IComputable[T]
        y-in as type IComputable[T]
        z-in as type IComputable[T].

       move x-in to self::_x
       move y-in to self::_y
       move z-in to self::_z
       goback
end method.

This method will only take IComputable instances which have been implemented with the same type as the Point3D class itself. Thus:

*> Given this:
        class-id ComputableFloat  implements type IComputable[float-long].
        class-id ComputableString implements type IComputable[string].

*> This is legal:

               01 vertex2 type Point3D[float-long].

               set vertex1 to new type Point3D[float-long]
               (
                   new type ComputableFloat(1)
                   new type ComputableFloat(1)
                   new type ComputableFloat(1)
               )
               01 vertex2 type Point3D[float-long].

*> But the compiler will reject this!

               set vertex1 to new type Point3D[float-long]
               (
                   new type ComputableString(1)
                   new type ComputableString(1)
                   new type ComputableString(1)
               )

*> It is rejected because the Point3D is parameterised to
*> float-long whilst the ComputableString is implements parametrised to
*> sting.

Hopefully I am managing to paint a picture in which everything is tied back to the same generic parameter and so nothing can be type unsafe. Rather than blather on any longer – here is a complete application:

*> The Whole Thing!
$set sourceformat(variable)

 class-id MessWithPoint3D

     method-id main static.
         01 vertex1 type Point3D[float-long].
         01 vertex2 type Point3D[float-long].

         set vertex1 to new type Point3D[float-long]
         (
             new type ComputableFloat(1)
             new type ComputableFloat(1)
             new type ComputableFloat(1)
         )

         set vertex2 to new type Point3D[float-long]
         (
             new type ComputableFloat(2)
             new type ComputableFloat(2)
             new type ComputableFloat(2)
         )

         Display type Point3D[float-long]::GetDistance(vertex1 vertex2)::GetValue

         *> This causes a compile error:
         *>  error COBCH0829 : Could not find method 'NEW' with this signature
         *> if uncommented - showing type safety is complete!
         *>set vertex2 to new type Point3D[float-long]
         *>(
         *>    new type ComputableString("2")
         *>    new type ComputableString("2")
         *>    new type ComputableString("2")
         *>)

     end method.

 end class.

 class-id Point3D using T.

     01 _x type IComputable[T].
     01 _y type IComputable[T].
     01 _z type IComputable[T].

     method-id get property x public.
         procedure division returning ret as type IComputable[T].
         move _x to ret
     end method.

     method-id get property y public.
         procedure division returning ret as type IComputable[T].
         move _y to ret
     end method.

     method-id get property z public.
         procedure division returning ret as type IComputable[T].
         move _z to ret
     end method.

     method-id GetDistance public static.
         01 inter type IComputable[T].
         procedure division
         using  by value
             startPoint as type Point3D[T]
             endPoint   as type Point3D[T]
         returning
             ret        as type IComputable[T].

             set inter to startPoint::x::Subtract(endPoint::x)::Square

             set inter to inter::Add
             (
                 startPoint::y::Subtract(endPoint::y)::Square
             )

             set inter to inter::Add
             (
                 startPoint::z::Subtract(endPoint::z)::Square
             )

             set ret to inter::Sqrt

     end method.

     *> The parameters of the new method link the type of IComputable to the
     *> type of the Point3D class and so fully enforce type safety
     method-id new public.

        procedure division
        using by value
             x-in as type IComputable[T]
             y-in as type IComputable[T]
             z-in as type IComputable[T].

            move x-in to self::_x
            move y-in to self::_y
            move z-in to self::_z
            goback
     end method.

 end class.

 interface-id IComputable using T.

    method-id #Add public.
        procedure division using by value
             toAdd as type IComputable[T]
             returning ret as type IComputable[T].
    end method.

    method-id #Subtract public.
        procedure division using by value
             toSubtract as type IComputable[T]
             returning ret as type IComputable[T].
    end method.

    method-id #Square public.
        procedure division returning ret as type IComputable[T].
    end method.

    method-id #Sqrt public.
        procedure division returning ret as type IComputable[T].
    end method.

    method-id GetValue public.
        procedure division returning ret as T.
    end method.

 end interface.

 class-id ComputableFloat implements type IComputable[float-long].

    01 my-value float-long.

    method-id new public.
        procedure division using by value in-value as float-long.
        move in-value to my-value
    end method.

    method-id #Add public.
        01 inter float-long.
        procedure division using by value
             toAdd as type IComputable[float-long]
             returning ret as type IComputable[float-long].

        compute inter =  toAdd::GetValue + my-value
        set ret to new ComputableFloat(inter)
    end method.

    method-id #Subtract public.
        01 inter float-long.
        procedure division using by value
             toAdd as type IComputable[float-long]
             returning ret as type IComputable[float-long].

        compute inter =  my-value - toAdd::GetValue
        set ret to new ComputableFloat(inter)
    end method.

    method-id #Square public.
        01 inter float-long.
        procedure division returning ret as type IComputable[float-long].
        compute inter = my-value * my-value
        set ret to new ComputableFloat(inter)
    end method.

    method-id #Sqrt public.
        01 inter float-long.
        procedure division returning ret as type IComputable[float-long].
        set inter to function sqrt(my-value)
        set ret to new ComputableFloat(inter)
    end method.

    method-id GetValue public.
        procedure division returning ret as float-long.
        move my-value to ret
    end method.

 end class.

 class-id ComputableString implements type IComputable[string].

    01 my-value string.
    01 my-float float-long.

    method-id new public.
        procedure division using by value in-value as string.
        move in-value to my-value
        set my-float to type System.Double::Parse(in-value)
    end method.

    method-id new public.
        procedure division using by value in-value as float-long.
        move in-value to my-float
        set my-value to my-float::ToString
    end method.

    method-id #Add public.
        01 f1 float-long.
        procedure division using by value
             toAdd as type IComputable[string]
             returning ret as type IComputable[string].
        set f1 to type System.Double::Parse(toAdd::GetValue)
        compute f1 =  f1 + my-float
        set ret to new ComputableString(f1::ToString)
    end method.

    method-id #Subtract public.
        01 f1 float-long.
        procedure division using by value
             toAdd as type IComputable[string]
             returning ret as type IComputable[string].
        set f1 to type System.Double::Parse(toAdd::GetValue)
        compute f1 =  my-float - f1
        set ret to new ComputableString(f1::ToString)
    end method.

    method-id #Square public.
        01 f1 float-long.
        procedure division returning ret as type IComputable[string].
        compute f1 = my-float * my-float
        set ret to new ComputableString(f1::ToString)
    end method.

    method-id #Sqrt public.
        01 f1 float-long.
        procedure division returning ret as type IComputable[string].
        set f1 to function sqrt(my-float)
        set ret to new ComputableString(f1::ToString)
    end method.

    method-id GetValue public.
        procedure division returning ret as string.
        set ret to new ComputableString(my-value)
    end method.

 end class.

Conclusions

Anything created by humans can be broken by humans. I suspect that somehow, someone, somewhere will be able to find a way to make my code type unsafe. However, I have not yet thought of it. In general, it is my assertion that if one uses generics in such a way that one does not require casts (X as type Y) then it is possible to use all the benefits of inheritance and polymorphism of OO coding and also have a completely type safe development style. It will take a bit of effort to get into the swing of using this style from scratch - but I think it is effort well worth putting in!

Also – please note that the example code here is not supposed to be a good mathematical implementation – the whole point is to illustrate coding style!

License

This article, along with any associated source code and files, is licensed under The Creative Commons Attribution-ShareAlike 2.5 License


Written By
Web Developer
United Kingdom United Kingdom
I am now a Software Systems Developer - Senior Principal at Micro Focus Plc. I am honoured to work in a team developing new compiler and runtime technology for Micro Focus.

My past includes a Ph.D. in computational quantum mechanics, software consultancy and several/various software development and architecture positions.

For more - see

blog: http://nerds-central.blogspot.com

twitter: http://twitter.com/alexturner

Comments and Discussions

 
-- There are no messages in this forum --