Click here to Skip to main content
15,881,248 members
Articles / Programming Languages / F#

Calling F# from COBOL and Back Again

Rate me:
Please Sign up or sign in to vote.
5.00/5 (3 votes)
9 Jan 2010CC (ASA 2.5)11 min read 20.1K   3  
Showing how Micro Focus Managed COBOL can call F#, and some tips on mixing imperative and functional languages the easy way.

Introduction

Running languages on .NET is ultra-powerful. Using managed COBOL (from Micro Focus), it is possible to use F# code to work with COBOL code. Imagine a Cloud based F# map reduce system consuming legacy COBOL - yes, that really is on the horizon.

There is a lot of interest around functional languages at the moment. I suspect one of the big drivers for this is that functional programming maps onto massively parallel and massively distributed processing models easily. These processing models are becoming more in vogue due to the ascendency of the Cloud and multi-core technologies. It is interesting, in this light, then to note that Microsoft has made their F# functional programming language part of the core .NET offering in Visual Studio 2010.

What really caught my interest was to see how easy it would be to make a COBOL program work with F#. To do so, I have used a not yet released version of the Micro Focus .NET COBOL running inside Visual Studio 2010. The project was a lot of fun, and it has proven to me that getting legacy or new COBOL code to interoperate with F# is a very practical thing to do.

In the image above, we can see F# in Visual Studio 2010 (beta), and below, COBOL in the same IDE.

Setting up a test situation

I have to admit I am no F# guru (and then some), so I had to come up with a simple example of something in F# which could act as a minimal analogue of a full map-reduce or similar framework. The option I went for is a simple quick sort based on the 'Comparable' interface (i.e., it will sort a list of objects which implement the interface) and a recursive function to print out the contents of a list in a user readable form. One can imagine these as analogues for a distributed processing algorithm and then a distributed storage algorithm just like those required in Cloud or grid computing. Once an easy way of achieving COBOL talking to these is done, getting it to work with map-reduce should be a simple matter of extension of principles.

A note on types

One of the things which makes functional languages in general, and F# in this case, good for distributed programming is that they are well suited to working with immutable structures. In imperative languages (like COBOL), we tend to work with mutable structures; we create a list and add elements to it, or create an integer variable and update it. Functional programming provides an intuitive way of dealing with structures which, once created, do not change; such structures are call immutable.

If a structure exists on more than one node of distributed system (or in the cache memory of more than one core in a multi-core system) and then that structure is mutated, the mutation must be propagated to all the places the structure is stored. This burdens the system with a need to track and update distributed structures. However, if a structure is immutable, then once distributed, the different nodes or cores can work with it without this overhead.

The upshot of all this is that F# has a bunch of immutable types built into its syntax. Like many functional programming languages (see VSPL as a very simple example: VSPL index page), F# has list handling built into its syntactical and semantic structure at a very intimate level. [] will create an empty list, and [1,2,3,4,5] will create a list of five elements. These lists are immutable lists. Because F# is a CLR (Common Language Runtime) language, it expresses those immutable lists as CLR (.NET) types. In this case, they are actually Microsoft.Microsoft.FSharp.Collections.FSharpList[type t] generic classes.

It is very unnatural to COBOL, C#, or VB to use these immutable types. Thus, one of the first things I found out about mixing COBOL with F# is that writing little type conversion functions in F# really helps. For example, the function below converts a System.Collections.Generic.List into an F# immutable list.

fs
let toList seq =
     Seq.toList seq

Which is called from COBOL thus:

01 flist type Microsoft.FSharp.Collections.FSharpList[type COBOLFSharp.CustomerRecord].
...
set flist to  type ComparableQuickSort::toList(testList)

In the example COBOL program, I did not actually have to expressly put the type of the F# style immutable list anywhere. I chose to code thus:

fs
set flist to  type ComparableQuickSort::toList(testList)
set flist to  type ComparableQuickSort::quicksort(flist)
invoke  type ComparableQuickSort::print_list(flist)

But could have done:

fs
invoke type ComparableQuickSort::print_list
(
    type ComparableQuickSort::quicksort
    (
        type ComparableQuickSort::toList(testList)
    )
)

Which causes the Micro Focus COBOL compiler to infer the types being passed around and use those to create the correct concrete types from the generics. This shows the compiler can behave much as a type inferring functional compiler. Indeed, doesn't that show just how sophisticated the MF compiler has now become?

The above code also shows how simple F# functions are accessed from COBOL. If they return nothing (), then we can use the invoke verb, and if they return a value, we can use the set verb or put them in line in the argument list of an invoke or set phrase. F# functions which are in an F# module are seen from COBOL as static methods on a class with the same name as the module (much like functions in a VB module are).

How do the F# functions work

I'll try to explain what the F# functions are doing; however, I am no F# expert, so this is very much F# 101, not F# advanced!

fs
let rec print_list l =
     match l with
     | [] -> ()
     | h::t ->
           print_head h
           print_list t

OK, this defines a function via the let verb with the name print_list. The function is recursive via the rec verb. If the rev verb was not there, then it could not call itself (the place at which it appears to call itself, it would actually be calling a new local definition of a function which happened to have the same name). The function takes a list as an argument and returns nothing. It prints out the contents of the list, one element at a time, starting with the first element.

It achieves this one element at a time thing via 'tail recursion'. The match verb in the function matches the argument to the function to different patterns. In this case, there are two patterns, either a list with elements, or an empty list. The empty list pattern is []. The list with elements pattern is h::t. h::t has a special meaning; it means head and tail where the first element of the list is the head and any remaining elements are put in a new list which is called the tail. Because we call print_head h, the head element gets printed each time. Because we call print_list t, any other elements get passed into the function to have another go. When there are no more elements, the tail is an empty list and the [] pattern is matched. This stops the recursion and returns (). () is nothing (a no element tuple), and that nothing gets passed all the way back until it is the final return of the original call.

In most imperative languages, this recursive definition of printing a list would be quite inefficient. The mechanisms for calling a function, with all the pushes and pops on and off the stack, would have to be called for each element of the list. In a functional programming language, the compiler should be able to work out that tail recursion is being used and compile the recursive function to a simple loop. I don't actually know if the F# compiler does this - but I really hope it does!

And the quick sort?

fs
let rec quicksort l =
     match l with
     |[] -> []
     |h::t -> quicksort (List.filter ((<) h) t) @ [h] @ 
                    (quicksort (List.filter ((>=) h) t))

This works using recursion in a similar way to the print_list function. However, it does not use tail recursion, it uses list splitting around a pivot. The head element is taken as the pivot. The passed list's tail is split into two lists: one where all the elements are less in value than the head, and one where they are greater or equal in value to the head. These two lists are then passed to quick sort. The result of the quick sorts of the sub lists is concatenated on either side of the head. This results in a tree like recursion, each branch of which starts to unwind when the passed sub list is empty. Rather than returning nothing () in this case (as print_list does), this algorithm returns an empty list [] which allows concatenation of the return.

And the type inference?

It is only whilst writing this up that I realised how much was actually going on which needs to be explained. No wonder getting this to work the first time gave me a headache. I think this is one of those 'easy when you know how' things.

Anyhow, in both these cases, the compiler can work out that the functions take lists because they manipulate the passed value using list operators. Thus, the compiler makes the parameter type a generic list. The print_list function only returns from recursion from the [] pattern; this pattern returns nothing (), so the compiler 'knows' that the function returns nothing. In the case of the quick sort, it 'knows' that the return is a list from a similar deduction. It also knows that the returned list will be of the same concrete type as the passed list as it is constructed from the same elements (just in a different order).

When these functions are called from COBOL, the COBOL compiler 'sees' them as generic types in the CLR. It can then use CLR and COBOL specific rules to work out how to invoke them. Because they are generic, the invoke parameter and return types are safe, but do not need to be defined in F# or in COBOL; they are inferred from the types of the parameters to the invokes. Thus, the F# and COBOL type inference systems work seamlessly together - neat!

The complete F# example:

fs
module ComparableQuickSort

let rec quicksort l =
     match l with
     |[] -> []
     |h::t -> quicksort (List.filter ((<) h) t) @ [h] 
                @ (quicksort (List.filter ((>=) h) t))

let rec print_head h = printfn "%A" h

let rec print_list l =
     match l with
     | [] -> ()
     | h::t ->
           print_head h
           print_list t

let toList seq =
     Seq.toList seq

Now for the COBOL

When I wrote the COBOL code, I had in my mind the idea that this might come from some pre-existing warehouse management system. The idea being that the 'picks' (someone going and getting something from the warehouse) were being recorded in some COBOL VSAM file, and we wanted to use our clever F# framework to processes them in a Cloud environment.

01 cust-grp property all.
03 pick-record-1 pic 9(4).
03 pick-record-2 pic x.
03 pick-sku      pic 9(8).

The idea is that the VSAM file stores picked records in a group like the one above. The sku being the stock keeping unit (unique identifier) for the item being picked. record-1 is a unique identifier for the customer order on that day, and record-2 could be A or B. Picks are always tried from the main warehouse first, which produces an A record. If the item is not found in the main warehouse, then an attempt is made to pick it from the second warehouse, and so a B record is also produced. Sorting of these records is done by the record-1 first, then the sku, and finally, B records must come after A records.

To implement this logic, I have created an object to encapsulate the group. We can see that I have then placed property all on the group. This makes all the items of the group to be exposed as properties on the object. Now, the legacy COBOL group semantics are fully intermeshed with the CLR type system! I have implemented the sort order logic in COBOL by making the class containing the group implement the Comparable interface.

This example is all 'made up'. If we were to do this with real legacy code, the class which creates the objects which we would pass to F# could then use Call verbs to interact with the legacy code. Such an approach would allow the .NET logic to act as a thin wrapper around the legacy code to make it interact with our new framework.

Most of the actual program in this example is just putting example data into the CustomerRecord objects! The bit which interacts with F# is just the last three lines before the final go back.

All this means that COBOL calls F#, which then calls back into COBOL! I.e., the ToString() and CompareTo methods of the CustomerRecord object (written in COBOL) are called from F# from functions which are called from COBOL. Now - that is language interop!

COBOL
program-id. TestQuickSort as "COBOLFSharp.TestQuickSort".

data division.
working-storage section.
01 testList type 
 System.Collections.Generic.List[type COBOLFSharp.CustomerRecord].
01 cus-rec  type COBOLFSharp.CustomerRecord.
01 i binary-long.
01 y binary-long.
01 flist type 
 Microsoft.FSharp.Collections.FSharpList[type COBOLFSharp.CustomerRecord].
procedure division.
  set testList to 
      new System.Collections.Generic.List[type COBOLFSharp.CustomerRecord]
  perform varying i from 0 by 1 until i = 24
      compute y = (function mod( i 4)) + i * 10
      compute y = y  * 123 + y
      compute y = 11111111 b-xor y
      set cus-rec to new Type COBOLFSharp.CustomerRecord
      set cus-rec::pick-sku to y
      set cus-rec::pick-record-1 to i
      set cus-rec::pick-record-2 to "A"
      invoke testList::Add(cus-rec)
      if function mod(i 3) = 0 then
          set cus-rec to new Type COBOLFSharp.CustomerRecord
          set cus-rec::pick-sku to y
          set cus-rec::pick-record-1 to i
          set cus-rec::pick-record-2 to "B"
          invoke testList::Add(cus-rec)              
      end-if
  end-perform
  set flist to  type ComparableQuickSort::toList(testList)
  set flist to  type ComparableQuickSort::quicksort(flist)
  invoke  type ComparableQuickSort::print_list(flist)

  goback.
end program TestQuickSort.

class-id. CustomerRecord
as "COBOLFSharp.CustomerRecord"
implements type System.IComparable.

  working-storage section.
  01 cust-grp property all.
     03 pick-record-1 pic 9(4).
     03 pick-record-2 pic x.
     03 pick-sku      pic 9(8).

  method-id. CompareTo public.
  local-storage section.
     01 toCheck type COBOLFSharp.CustomerRecord.
  procedure division using by value toWhat 
     as object returning result as binary-long.
     *> Anything which is the wrong type is assumed equals (logical absurdity)      if not toWhat instance of type COBOLFSharp.CustomerRecord then
         move 0 to result
         goback
     end-if
     set toCheck to toWhat as type COBOLFSharp.CustomerRecord
     if self::pick-record-1 > toCheck::pick-record-1 then
         move 1 to result
         goback
     end-if
     if self::pick-record-1 < toCheck::pick-record-1 then
         move -1 to result
         goback
     end-if
     *> Same pick - order by sku      if self::pick-sku > toCheck::pick-sku then
         move 1 to result
         goback
     end-if
     if self::pick-sku < toCheck::pick-sku then
         move -1 to result
         goback
     end-if
     *> Move all b records to be after all a records      if self::pick-record-2 = toCheck::pick-record-2 then
         move 0 to result
         goback
     end-if
     if self::pick-record-2 = "A" then
         move 1 to result
         goback
     end-if
    
     move -1 to result
     goback      
  end method.
 
  method-id. ToString override.
  procedure division returning stringVal as string.
      set stringVal to 
      String::Format("{0}/{1}/{2}" pick-record-1 pick-sku pick-record-2)
  end method.

end class.

Conclusions

Calling F# from COBOL is very doable. It does require a little bit of getting used to, and I would recommend spending the time to design the 'touch points' between the two languages easy to work with. For example, just implementing the toList function made the programming much easier. If approached with this in mind, I see that F# and COBOL can play very well together, each having strengths which complement the other.

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 --