A Comparison Of .net COBOL, Visual Basic and C#






4.72/5 (18 votes)
A simple table showing the syntactic conversion from between each of these languages.
Introduction
If you are a COBOL programmer wanting to learn C# or a VB programmer wanting to learn COBOL as a .net language (or any other combination of VB.net, C# and COBOL) then this is a good place to start.
Background
It has often been noted that the richness of the COBOL language in its Micro Focus .net implementation is not well known. Robert Sales and I have worked on this document to help bring the language to peoples' attention and to help people who need to work with COBOL on the .net platform
Using the code
All the examples where should work in the appropriate Visual Studio IDE. You can get a free version here http://download.cnet.com/Net-Express-with-NET/3000-2069_4-10866201.html?part=dl-10866201&subj=dl&tag=button.
VB.NET | C# | COBOL |
---|---|---|
Program Structure | ||
Imports System Namespace Hello Class HelloWorld Overloads Shared Sub Main(ByVal args() As String) Dim name As String = "VB.NET" 'See if an argument was passed from the command line If args.Length = 1 Then name = args(0) End If Console.WriteLine("Hello, " & name & "!") End Sub End Class End Namespace End Class |
using System; namespace Hello { public class HelloWorld { public static void Main(string[] args) { string name = "C#"; // See if an argument was passed from the command line if (args.Length == 1) { name = args[0]; } Console.WriteLine("Hello, " + name + "!"); } } } |
$set sourceformat(free) $set ilusing"System" *> Note, no direct syntax for specifying a default namespace; class-id. HelloWorld as "Hello.Helloworld". static. method-id. Main. local-storage section. 01 nam string. procedure division using by value args as string occurs any. *> See if an argument was passed from the command line if args::"Length" = 1 set nam to args(1) end-if display "Hello, ", nam, "!" *> or, if preferred... invoke type "Console"::"WriteLine"(string::"Concat"("Hello, ", nam, "!")) end method Main. end static. end class HelloWorld. |
Comments | ||
' Single line only REM Single line only ''' <summary>XML comments</summary> |
// Single line /* Multiple line */ /// <summary>XML comments on single line</summary> /** <summary>XML comments on multiple lines</summary> */</span> |
* Single line only, "old-style" COBOL comment with '*' in column 7 *> inline comment may follow Cobol statements etc. *>> <summary>XML comments</summary> |
Data Types | ||
Value Types Boolean Byte, SByte Char Short, UShort, Integer, UInteger, Long, ULong Single, Double Decimal Date Reference Types Object String Initializing Dim correct As Boolean = True Dim b As Byte = &H2A 'hex Dim o As Byte = &O52 'octal Dim person As Object = Nothing Dim name As String = "Dwight" Dim grade As Char = "B"c Dim today As Date = #12/31/2007 12:15:00 PM# Dim amount As Decimal = 35.99@ Dim gpa As Single = 2.9! Dim pi As Double = 3.14159265 Dim lTotal As Long = 123456L Dim sTotal As Short = 123S Dim usTotal As UShort = 123US Dim uiTotal As UInteger = 123UI Dim ulTotal As ULong = 123UL Type Information Dim x As Integer Console.WriteLine(x.GetType()) ' Prints System.Int32 Console.WriteLine(GetType(Integer)) ' Prints System.Int32 Console.WriteLine(TypeName(x)) ' Prints Integer Type Conversion Dim d As Single = 3.5 Dim i As Integer = CType(d, Integer) ' set to 4 (Banker's rounding) i = CInt(d) ' same result as CType i = Int(d) ' set to 3 (Int function truncates the decimal) |
Value Types bool byte, sbyte char short, ushort, int, uint, long, ulong float, double decimal DateTime (not a built-in C# type) Reference Types object string Initializing bool correct = true; byte b = 0x2A; // hex object person = null; string name = "Dwight"; char grade = 'B'; DateTime today = DateTime.Parse("12/31/2007 12:15:00"); decimal amount = 35.99m; float gpa = 2.9f; double pi = 3.14159265; long lTotal = 123456L; short sTotal = 123; ushort usTotal = 123; uint uiTotal = 123; ulong ulTotal = 123; Type Information int x; Console.WriteLine(x.GetType()); // Prints System.Int32 Console.WriteLine(typeof(int)); // Prints System.Int32 Console.WriteLine(x.GetType().Name); // prints Int32 Type Conversion float d = 3.5f; int i = (int)d; // set to 3 (truncates decimal) |
Value Types condition-value binary-char (unsigned) character binary-short, binary-long, binary-double (unsigned) float-short, float-long decimal DateTime (not a built-in COBOL type Reference types object string Initializing 01 correct condition-value value true. 01 b binary-char unsigned value h"2a". *> Hex 01 o binary-char ussigned value o"52". *> Octal 01 person object value null. 01 nam string value "Dwight". 01 grade character value "B". 01 today type "DateTime" value type "DateTime"::"Parse"("12/31/2007 12:15:00"). 01 amount decimal value 35.99. 01 gpa float-short value 2.9. 01 pi float-long value 3.14159265. 01 lTotal binary-double value 123456. 01 sTotal binary-short value 123. 01 usTotal binary-short unsigned value 123. 01 uiTotal binary-long value 123. 01 ulTotal binary-long unsigned value 123. Type Information 01 x binary-long. display x::"GetType" *> Prints System.Int32 display type of binary-long *> Prints System.Int32 display x::"GetType"::"Name" *> Prints Int32 Type Conversion 01 d float-short value 3.5. *> automatic conversion set i to d as binary-long *> set to 3 (truncates decimal) COBOL types not supported in C# or VB.Net *> Only a few examples here 01 displayNumber pic 9(9).99. 01 computeNumber pic 9(9)V99. 01 alphaNumberic pic a(23). 01 binaryStorage pic x(12). *> Also groups and redefines - a few examples 01 arecord. 03 aSubRecord pic x(10). 03 aUnion pic 9(10) redefines aSubrecord. |
Constants | ||
Const MAX_STUDENTS As Integer = 25 ' Can set to a const or var; may be initialized in a constructor ReadOnly MIN_DIAMETER As Single = 4.93 |
const int MAX_STUDENTS = 25; // Can set to a const or var; may be initialized in a constructor readonly float MIN_DIAMETER = 4.93f; |
78 MAX_STUDENTS value 25. *> optionally public, binary-long... *> Currently no direct COBOL equivalent of 'readonly' |
Enumeration | ||
Enum Action Start [Stop] ' Stop is a reserved word Rewind Forward End Enum Enum Status Flunk = 50 Pass = 70 Excel = 90 End Enum Dim a As Action = Action.Stop If a <> Action.Start Then _ Console.WriteLine(a.ToString & " is " & a) ' Prints "Stop is 1" Console.WriteLine(Status.Pass) ' Prints 70 Console.WriteLine(Status.Pass.ToString()) ' Prints Pass |
enum Action {Start, Stop, Rewind, Forward}; enum Status {Flunk = 50, Pass = 70, Excel = 90}; Action a = Action.Stop; if (a != Action.Start) Console.WriteLine(a + " is " + (int) a); // Prints "Stop is 1" Console.WriteLine((int) Status.Pass); // Prints 70 Console.WriteLine(Status.Pass); // Prints Pass |
*> enum Action... enum-id. Action. 78 #Start. *> Start is a reserved word 78 #Stop. 78 #Rewind. 78 #Forward. end enum Action. *>enum Status... enum-id. Stat as "Status". 78 Flunk value 50. 78 Pass value 70. 78 Excel value 90. end enum Action. display type "Status"::"Pass" as binary-long *> prints 70 display type "Status"::"Pass" *> prints PassSee demo program |
Operators | ||
Comparison = < > <= >= <> Arithmetic + - * / Mod \ (integer division) ^ (raise to a power) Assignment = += -= *= /= \= ^= <<= >>= &= Bitwise And Or Xor Not << >> Logical AndAlso OrElse And Or Xor Not 'Note: AndAlso and OrElse perform short-circuit logical evaluations String Concatenation & |
Comparison == < > <= >= != Arithmetic + - * / % (mod) / (integer division if both operands are ints) Math.Pow(x, y) Assignment = += -= *= /= %= &= |= ^= <<= >>= ++ -- Bitwise & | ^ ~ << >> Logical && || & | ^ ! //Note: && and || perform short-circuit logical evaluations String Concatenation + |
Comparison = < > <= >= <> Arithmetic + - * / function mod *>no direct COBOL equivalent to integer division ** Assignment move, set, compute Bitwise b-and, b-or, b-xor, b-not, b-left, b-right Logical and, or, not |
Choices | ||
greeting = IIf(age < 20, "What's up?", "Hello") ' One line doesn't require "End If" If age < 20 Then greeting = "What's up?" If age < 20 Then greeting = "What's up?" Else greeting = "Hello" ' Use : to put two commands on same line If x <> 100 And y < 5 Then x *= 5 : y *= 2 ' Preferred If x <> 100 And y < 5 Then x *= 5 y *= 2 End If ' To break up any long single line use _ If whenYouHaveAReally < longLine And _ itNeedsToBeBrokenInto2 > Lines Then _ UseTheUnderscore(charToBreakItUp) If x > 5 Then x *= y ElseIf x = 5 Then x += y ElseIf x < 10 Then x -= y Else x /= y End If Select Case color ' Must be a primitive data type Case "pink", "red" r += 1 Case "blue" b += 1 Case "green" g += 1 Case Else other += 1 End Select |
greeting = age < 20 ? "What's up?" : "Hello"; // Good practice is that all consequents are enclosed in {} // or are on the same line as if. if (age < 20) greeting = "What's up?"; else { greeting = "Hello"; } // Multiple statements must be enclosed in {} if (x != 100 && y < 5) { x *= 5; y *= 2; } //No need for _ or : since ; is used to terminate each statement. if (x > 5) { x *= y; } else if (x == 5) { x += y; } else if (x < 10) { x -= y; } else { x /= y; } // Every case must end with break or goto case switch (color) // Must be integer or string { case "pink": case "red": r++; break; case "blue": b++; break; case "green": g++; break; default: other++; break; // break necessary on default } |
*>greeting = age < 20 ? has no directly equivalent syntax in COBOL if age < 20 move "What's up?" to greeting else move "Hello" to greeting end-if if x not = 100 and y < 5 multiply 5 by x multiply 2 by y end-if *>No need for _ or : since statement is terminated by end-if *> evalute is prefered in COBOL rather than if/else if/else evaluate x when > 5 multiply y by x when 5 add y to x when < 10 subtract y from x when other divide y into x end-evaluate evaluate color *> can be any type when "pink" when "red" add 1 to r when "blue" add 1 to b when "green" add 1 to g when other add 1 to other-color end-evaluateSee demo program |
Loops | ||
Pre-test Loops: While c < 10 c += 1 End While Do Until c = 10 c += 1 Loop Do While c < 10 c += 1 Loop For c = 2 To 10 Step 2 Console.WriteLine(c) Next Post-test Loops: Do c += 1 Loop While c < 10 Do c += 1 Loop Until c = 10 Array or collection looping Dim names As String() = {"Fred", "Sue", "Barney"} For Each s As String In names Console.WriteLine(s) Next Breaking out of loops Dim i As Integer = 0 While (True) If (i = 5) Then Exit While End If i += 1 End While Continue to next iteration For i = 0 To 4 If i < 4 Then Continue For End If Console.WriteLine(i) ' Only prints 4 Next |
Pre-test Loops: // no "until" keyword while (c < 10) { c++; } for (c = 2; c <= 10; c += 2) { Console.WriteLine(c); } Post-test Loop: do { c++; } while (c < 10); Array or collection looping string[] names = {"Fred", "Sue", "Barney"}; foreach (string s in names) { Console.WriteLine(s); } Breaking out of loops int i = 0; while (true) { if (i == 5) { break; } i++; } Continue to next iteration for (i = 0; i < 5; i++) { if (i < 4) { continue; } Console.WriteLine(i); // Only prints 4 } |
Pre-test loops: *> No WHILE keyword perform until c >= 10 add 1 to c end-perform perform varying c from 2 by 2 until c > 10 display c end-perform Post-test loops: perform with test after until c >= 10 add 1 to c end-perform Array or collection looping 01 names string occurs any. 01 s string. set content of names to ("Fred" "Sue" "Barney") perform varying s through names display s end-perform Breaking out of loops: 01 i binary-long value 0. perform until exit if i = 5 exit perform end-if add 1 to i end-perform Continue to next iteration: 01 i binary-long value 0 perform varying i from 0 by 1 until i >= 5 if i < 4 exit perform cycle end-if display i *>Only prints 4 end-performSee demo program |
Arrays | ||
Dim nums() As Integer = {1, 2, 3} For i As Integer = 0 To nums.Length - 1 Console.WriteLine(nums(i)) Next ' 4 is the index of the last element, so it holds 5 elements Dim names(4) As String names(0) = "David" names(5) = "Bobby" ' Throws System.IndexOutOfRangeException ' Resize the array, keeping the existing values (Preserve is optional) ' Note however, that this produces a new copy of the array - it is not an in-place resize! ReDim Preserve names(6) Dim twoD(rows-1, cols-1) As Single twoD(2, 0) = 4.5 Dim jagged()() As Integer = { _ New Integer(4) {}, New Integer(1) {}, New Integer(2) {} } jagged(0)(4) = 5 |
int[] nums = {1, 2, 3}; for (int i = 0; i < nums.Length; i++) { Console.WriteLine(nums[i]); } // 5 is the size of the array string[] names = new string[5]; names[0] = "David"; names[5] = "Bobby"; // Throws System.IndexOutOfRangeException // C# can't dynamically resize an array. Just copy into new array. string[] names2 = new string[7]; Array.Copy(names, names2, names.Length); // or names.CopyTo(names2, 0); float[,] twoD = new float[rows, cols]; twoD[2,0] = 4.5f; int[][] jagged = new int[3][] { new int[5], new int[2], new int[3] }; jagged[0][4] = 5; |
01 nums binary-long occurs any values 1, 2, 3. *> Can also do: set content of nums to (1 2 3) *> 5 is the size of the array 01 names string occurs 5. *> Can also do: 01 names string occurs any. set size of names to 5 set names(1) to "David" *> first element indexed as 1 set names(6) to "Bobby" *> throws System.IndexOutOfRangeException *> COBOL cannot resize an array - use copy 01 names2 string occurs 7. invoke type "Array"::"Copy"(names, names2, names::"Length") *> or else: invoke names::"CopyTo"(names2, 0) 01 twoD float-short occurs any, any. set size of twoD to rows, cols 01 jagged binary-long occurs any, occurs any. set size of jagged to 3 set size of jagged(1) to 5 set jagged(1 5) to 5See demo program |
Functions | ||
' Pass by value (in, default), reference (in/out), and reference (out) Sub TestFunc(ByVal x As Integer, ByRef y As Integer, ByRef z As Integer) x += 1 y += 1 z = 5 End Sub Dim a = 1, b = 1, c As Integer ' c set to zero by default TestFunc(a, b, c) Console.WriteLine("{0} {1} {2}", a, b, c) ' 1 2 5 ' Accept variable number of arguments Function Sum(ByVal ParamArray nums As Integer()) As Integer Sum = 0 For Each i As Integer In nums Sum += i Next End Function ' Or use Return statement like C# Dim total As Integer = Sum(4, 3, 2, 1) ' returns 10 ' Optional parameters must be listed last and must have a default value Sub SayHello(ByVal name As String, Optional ByVal prefix As String = "") Console.WriteLine("Greetings, " & prefix & " " & name) End Sub SayHello("Strangelove", "Dr.") SayHello("Madonna") |
// Pass by value (in, default), reference (in/out), and reference (out) void TestFunc(int x, ref int y, out int z) { x++; y++; z = 5; } int a = 1, b = 1, c; // c doesn't need initializing TestFunc(a, ref b, out c); Console.WriteLine("{0} {1} {2}", a, b, c); // 1 2 5 // Accept variable number of arguments int Sum(params int[] nums) { int sum = 0; foreach (int i in nums) { sum += i; } return sum; } int total = Sum(4, 3, 2, 1); // returns 10 /* C# doesn't support optional arguments/parameters. Just create two different versions of the same function. */ void SayHello(string name, string prefix) { Console.WriteLine("Greetings, " + prefix + " " + name); } void SayHello(string name) { SayHello(name, ""); } |
method-id. TestFunc. procedure division using by value x as binary-long, by reference y as binary-long, output z as binary-long. add 1 to x, y move 5 to z end method TestFunc. 01 a binary-long value 1. 01 b binary-long value 1. 01 c binary-long. *> c doesn't need initializing invoke self::"TestFunc"(value a reference b output c) *> Or invoke self::"TestFunc"(a b c) display a space b space c *> sum is an intrinsic function in COBOL 01 total binary-long. set total to function sum(4 3 2 1) *> returns 10 *> To create a non intrinsic variable argument list function: Method-id. MySum. 01 i binary-long. Procedure division using params nums as binary-long occurs any returning mysum as binary-long. Perform varying i through nums Add i to mysum End-perform Goback End method MySum. *> then to call it: method-id. main. 01 i binary-long. set i to self::"MySum"(1 2 3 4) display i end method main. *> COBOL doesn't support optional arguments/parameters. *> Just create two different versions of the same function. method-id. SayHello. procedure division using by value nam as string, prefix as string. display "Greetings, " prefix space nam end method SayHello. method-id. SayHello. procedure division using by value nam as string. invoke self::"SayHello"(nam "") end method SayHello.See demo program A See demo program B |
Strings | ||
Special character constants (all also accessible from ControlChars class) vbCrLf, vbCr, vbLf, vbNewLine vbNullString vbTab vbBack vbFormFeed vbVerticalTab "" ' String concatenation (use & or +) Dim school As String = "Harding" & vbTab school = school & "University" ' school is "Harding (tab) University" ' Chars Dim letter As Char = school.Chars(0) ' letter is H letter = Convert.ToChar(65) ' letter is A letter = Chr(65) ' same thing Dim word() As Char = school.ToCharArray() ' word holds Harding ' No string literal operator Dim msg As String = "File is c:\temp\x.dat" ' String comparison Dim mascot As String = "Bisons" If (mascot = "Bisons") Then ' true If (mascot.Equals("Bisons")) Then ' true If (mascot.ToUpper().Equals("BISONS")) Then ' true If (mascot.CompareTo("Bisons") = 0) Then ' true ' String matching with Like - Regex is more powerful If ("John 3:16" Like "Jo[Hh]? #:*") Then 'true ' Substring s = mascot.Substring(2, 3)) ' s is "son" ' Replacement s = mascot.Replace("sons", "nomial")) ' s is "Binomial" ' Split Dim names As String = "Frank,Becky,Ethan,Braden" Dim parts() As String = names.Split(",".ToCharArray()) ' One name in each slot ' Date to string Dim dt As New DateTime(1973, 10, 12) Dim s As String = "My birthday: " & dt.ToString("MMM dd, yyyy") ' Oct 12, 1973 ' Integer to String Dim x As Integer = 2 Dim y As String = x.ToString() ' y is "2" ' String to Integer Dim x As Integer = Convert.ToInt32("-5") ' x is -5 ' Mutable string Dim buffer As New System.Text.StringBuilder("two ") buffer.Append("three ") buffer.Insert(0, "one ") buffer.Replace("two", "TWO") Console.WriteLine(buffer) ' Prints "one TWO three" |
Escape sequences \r // carriage-return \n // line-feed \t // tab \\ // backslash \" // quote // String concatenation string school = "Harding\t"; school = school + "University"; // school is "Harding (tab) University" // Chars char letter = school[0]; // letter is H letter = Convert.ToChar(65); // letter is A letter = (char)65; // same thing char[] word = school.ToCharArray(); // word holds Harding // String literal string msg = @"File is c:\temp\x.dat"; // same as string msg = "File is c:\\temp\\x.dat"; // String comparison string mascot = "Bisons"; if (mascot == "Bisons") // true if (mascot.Equals("Bisons")) // true if (mascot.ToUpper().Equals("BISONS")) // true if (mascot.CompareTo("Bisons") == 0) // true // String matching - No Like equivalent, use Regex // Substring s = mascot.Substring(2, 3)) // s is "son" // Replacement s = mascot.Replace("sons", "nomial")) // s is "Binomial" // Split string names = "Frank,Becky,Ethan,Braden"; string[] parts = names.Split(",".ToCharArray()); // One name in each slot // Date to string DateTime dt = new DateTime(1973, 10, 12); string s = dt.ToString("MMM dd, yyyy"); // Oct 12, 1973 // int to string int x = 2; string y = x.ToString(); // y is "2" // string to int int x = Convert.ToInt32("-5"); // x is -5 // Mutable string System.Text.StringBuilder buffer = new System.Text.StringBuilder("two "); buffer.Append("three "); buffer.Insert(0, "one "); buffer.Replace("two", "TWO"); Console.WriteLine(buffer); // Prints "one TWO three" |
Escape sequences x"0a" *> line-feed x"09" *> tab "\" *> backslash "" *> quote *> string concatenation 01 school string value "Harding" & x"09". set school to string::"Concat"(school, "University") *> school is "Harding (tab) University" *> Chars 01 letter character. 01 word character occurs any. set letter to school::"Chars"(0) *> letter is H set letter to type "Convert"::"ToChar"(65) *> letter is A set letter to 65 as character *> same thing set word to school::"ToCharArray" *>word holds Harding *> String literal 01 msg string value "File is c:\temp\x.dat". *>String comparison 01 mascot string value "Bisons". if mascot = "Bisons" *> true if mascot::"Equals"("Bisons") *> true if mascot::"ToUpper"::"Equals"("BISONS") *> true if mascot::"CompareTo"("Bisons") = 0 *> true *> String matching - no Like equivalent , use Regex *> Substring set s to mascot::"Substring"(2 3) *> s is "son" *> Replacement set s to mascot::"Replace"("sons" "nomial") *> s is "Binomial" *> Split 01 names string value "Frank,Becky,Ethan,Braden". 01 parts string occurs any. set parts to names::"Split"(",") *> Date to string 01 dt type "DateTime" value new "DateTime"(1973, 10, 12). 01 s string. set s to dt::"ToString"("MMM dd, yyyy") *> Oct 12, 1973 *> int to string 01 x string. 01 y binary-long value 2. set x to type x::"ToString" *> x is "2" *> string to int 01 x binary-long. set x to type "Convert"::"ToInt32"("-5") *> x is -5 *> Mutable string 01 buffer type "System.Text.StringBuilder" value new "System.Text.StringBuilder"("two "). invoke buffer::"Append"("three ") invoke buffer::"Insert"(0, "one ") invoke buffer::"Replace("two" "TWO" display buffer *> Prints "one TWO three"See demo program |
Exception Handling | ||
' Throw an exception Dim ex As New Exception("Something is really wrong.") Throw ex ' Catch an exception Try y = 0 x = 10 / y Catch ex As Exception When y = 0 ' Argument and When is optional Console.WriteLine(ex.Message) Finally Beep() End Try ' Deprecated unstructured error handling On Error GoTo MyErrorHandler ... MyErrorHandler: Console.WriteLine(Err.Description) |
// Throw an exception Exception up = new Exception("Something is really wrong."); throw up; // ha ha // Catch an exception try { y = 0; x = 10 / y; } catch (Exception ex) // Argument is optional, no "When" keyword { Console.WriteLine(ex.Message); } finally { Microsoft.VisualBasic.Interaction.Beep(); } |
*> Throw an exception 01 up type "Exception" value new "Exception"("Something is really wrong."); raise up *> ha ha *> Catch an exception try set y to 0; compute x = 10 / y catch (type "Exception" ex) *> Argument is optional, no "When" keyword display ex.Message finally invoke type "Microsoft.VisualBasic.Interaction"::"Beep" end-trySee demo program |
Namespaces | ||
Namespace Harding.Compsci.Graphics ... End Namespace ' or Namespace Harding Namespace Compsci Namespace Graphics ... End Namespace End Namespace End Namespace Imports Harding.Compsci.Graphics |
namespace Harding.Compsci.Graphics { ... } // or namespace Harding { namespace Compsci { namespace Graphics { ... } } } using Harding.Compsci.Graphics; |
*> At the file level $set ilnamespace "Harding.Compsci.Graphics" *> The directive can also be set as a project *> level to apply the name space to all classes in the project. |
Classes / Interfaces | ||
' Accessibility keywords Public Private Friend Protected Protected Friend Shared ' Inheritance Class FootballGame Inherits Competition ... End Class ' Interface definition Interface IAlarmClock ... End Interface ' Extending an interface Interface IAlarmClock Inherits IClock ... End Interface ' Interface implementation Class WristWatch Implements IAlarmClock, ITimer ... End Class |
//Accessibility keywords public private internal protected protected internal static // Inheritance class FootballGame : Competition { ... } // Interface definition interface IAlarmClock { ... } // Extending an interface interface IAlarmClock : IClock { ... } // Interface implementation class WristWatch : IAlarmClock, ITimer { ... } |
*> Accessibility keywords public private internal protected protected internal static *> Inheritance class-id. FootballGame inherits type "Competition". ... end class FootballGame. *> Interface definition interface-id. IAlarmClock. ... end interface IAlarmClock. *> Extending an interface interface-id IAlarmClock extends type "IClock". ... end interface IAlarmClock. *> Interface implementation class-id. WristWatch implements type "IAlarmClock", type "ITimer". ... end class WristWatch.See demo program |
Constructors / Destructors | ||
Class SuperHero Private _powerLevel As Integer Public Sub New() _powerLevel = 0 End Sub Public Sub New(ByVal powerLevel As Integer) Me._powerLevel = powerLevel End Sub Protected Overrides Sub Finalize() ' Desctructor code to free unmanaged resources MyBase.Finalize() End Sub End Class |
class SuperHero { private int _powerLevel; public SuperHero() { _powerLevel = 0; } public SuperHero(int powerLevel) { this._powerLevel= powerLevel; } ~SuperHero() { // Destructor code to free unmanaged resources. // Implicitly creates a Finalize method } } |
class-id. SuperHero. 01 _powerLevel binary-long. method-id. new. procedure division. set _powerLevel to 0 end method new. method-id. new. procedure division using by value powerLevel as binary-long. set _powerLevel to powerLevel end method new. method-id. Finalize override protected. *> Destructor code to free unmanaged resources. end method Finalize. end class SuperHero.See demo program |
Using Objects | ||
Dim hero As SuperHero = New SuperHero ' or Dim hero As New SuperHero With hero .Name = "SpamMan" .PowerLevel = 3 End With hero.Defend("Laura Jones") hero.Rest() ' Calling Shared method ' or SuperHero.Rest() Dim hero2 As SuperHero = hero ' Both reference the same object hero2.Name = "WormWoman" Console.WriteLine(hero.Name) ' Prints WormWoman hero = Nothing ' Free the object If hero Is Nothing Then _ hero = New SuperHero Dim obj As Object = New SuperHero If TypeOf obj Is SuperHero Then _ Console.WriteLine("Is a SuperHero object.") ' Mark object for quick disposal Using reader As StreamReader = File.OpenText("test.txt") Dim line As String = reader.ReadLine() While Not line Is Nothing Console.WriteLine(line) line = reader.ReadLine() End While End Using |
SuperHero hero = new SuperHero(); // No "With" construct hero.Name = "SpamMan"; hero.PowerLevel = 3; hero.Defend("Laura Jones"); SuperHero.Rest(); // Calling static method SuperHero hero2 = hero; // Both reference the same object hero2.Name = "WormWoman"; Console.WriteLine(hero.Name); // Prints WormWoman hero = null ; // Free the object if (hero == null) hero = new SuperHero(); Object obj = new SuperHero(); if (obj is SuperHero) { Console.WriteLine("Is a SuperHero object."); } // Mark object for quick disposal using (StreamReader reader = File.OpenText("test.txt")) { string line; while ((line = reader.ReadLine()) != null) { Console.WriteLine(line); } } |
01 hero type "SuperHero" value new "SuperHero". 01 hero2 type "SuperHero". 01 obj object. 01 reader type "StreamReader". 01 lin string. // No "With" construct set hero::"Name" to "SpamMan" set hero::"PowerLevel" to 3 invoke hero::"Defend"("Laura Jones") invoke type "SuperHero"::"Rest" *> Calling static method set hero2 to hero *> Both reference the same objectv set hero2::"Name" to "WormWoman" display hero::"Name" *> Prints WormWoman set hero to null *> Free the object if hero = null set hero to new "SuperHero" end-if set obj to new "SuperHero" if obj is instance of type "SuperHero" display "Is a SuperHero object." end-if *> No 'using' construct in COBOL try set reader to type "File"::"OpenText"("test.txt") perform until exit set lin to reader::"ReadLine" if lin = null exit perform end-if end-perform finally if reader not = null invoke reader::"Dispose" end-if end-trySee demo program |
Structs | ||
Structure StudentRecord Public name As String Public gpa As Single Public Sub New(ByVal name As String, ByVal gpa As Single) Me.name = name Me.gpa = gpa End Sub End Structure Dim stu As StudentRecord = New StudentRecord("Bob", 3.5) Dim stu2 As StudentRecord = stu stu2.name = "Sue" Console.WriteLine(stu.name) ' Prints Bob Console.WriteLine(stu2.name) ' Prints Sue |
struct StudentRecord { public string name; public float gpa; public StudentRecord(string name, float gpa) { this.name = name; this.gpa = gpa; } } StudentRecord stu = new StudentRecord("Bob", 3.5f); StudentRecord stu2 = stu; stu2.name = "Sue"; Console.WriteLine(stu.name); // Prints Bob Console.WriteLine(stu2.name); // Prints Sue |
$set sourceformat(free) preservecase valuetype-id. StudentRecord. object. 01 #name string public. 01 gpa float-short public. method-id. new. procedure division using by value nam as string, gpa as float-short. set #name to nam set self::"gpa" to gpa end method new. end object. end valuetype StudentRecord. class-id. a. static. method-id. main. 01 stu type "StudentRecord" value new "StudentRecord"("Bob", 3.5). 01 stu2 type "StudentRecord". procedure division. set stu2 to stu set stu2::"name" to "Sue" display stu::"name" *> Prints Bob display stu2::"name" *> Prints Sue end method main. end static. end class a.See demo program |
Properties | ||
Private _size As Integer Public Property Size() As Integer Get Return _size End Get Set (ByVal Value As Integer) If Value < 0 Then _size = 0 Else _size = Value End If End Set End Property foo.Size += 1 |
private int _size; public int Size { get { return _size; } set { if (value < 0) { _size = 0; } else { _size = value; } } } foo.Size++; |
$set sourceformat(free) preservecase class-id. MyClass. object. 01 _size binary-long private. method-id. get property #Size. procedure division returning ret as binary-long. set ret to _size end method. method-id. set property #Size. procedure division using by value val as binary-long. if val < 0 set _size to 0 else set _size to val end-if end method. end object. end class MyClass. class-id. a. static. method-id. main. 01 foo type "MyClass" value new"MyClass". add 1 to foo::"Size" display foo::"Size" end method main. end static. end class a.See demo program |
Delegates / Events | ||
Delegate Sub MsgArrivedEventHandler(ByVal message As String) Event MsgArrivedEvent As MsgArrivedEventHandler ' or to define an event which declares a delegate implicitly Event MsgArrivedEvent(ByVal message As String) AddHandler MsgArrivedEvent, AddressOf My_MsgArrivedCallback ' Won't throw an exception if obj is Nothing RaiseEvent MsgArrivedEvent("Test message") RemoveHandler MsgArrivedEvent, AddressOf My_MsgArrivedCallback Imports System.Windows.Forms Dim WithEvents MyButton As Button ' WithEvents can't be used on local variable MyButton = New Button Private Sub MyButton_Click(ByVal sender As System.Object, _ ByVal e As System.EventArgs) Handles MyButton.Click MessageBox.Show(Me, "Button was clicked", "Info", _ MessageBoxButtons.OK, MessageBoxIcon.Information) End Sub |
delegate void MsgArrivedEventHandler(string message); event MsgArrivedEventHandler MsgArrivedEvent; // Delegates must be used with events in C# MsgArrivedEvent += new MsgArrivedEventHandler(My_MsgArrivedEventCallback); MsgArrivedEvent("Test message"); // Throws exception if obj is null MsgArrivedEvent -= new MsgArrivedEventHandler(My_MsgArrivedEventCallback); using System.Windows.Forms; Button MyButton = new Button(); MyButton.Click += new System.EventHandler(MyButton_Click); private void MyButton_Click(object sender, System.EventArgs e) { MessageBox.Show(this, "Button was clicked", "Info", MessageBoxButtons.OK, MessageBoxIcon.Information); } |
$set sourceformat(free) preservecase $set ilusing"System" delegate-id. MsgArrivedEventHandler. procedure division using by value messag as string. end delegate MsgArrivedEventHandler. class-id. a. static. 01 MsgArrivedEvent type "MsgArrivedEventHandler" event. *> Delegates must be used with events in COBOL method-id. main. set MsgArrivedEvent to type "Delegate"::"Combine" ( MsgArrivedEvent, new "MsgArrivedEventHandler"(self::"My_MsgArrivedEventCallback") ) as type "MsgArrivedEventHandler" invoke MsgArrivedEvent::"Invoke"("Test message") *> Throws exception if obj is null set MsgArrivedEvent to type "Delegate"::"Remove" ( MsgArrivedEvent, new "MsgArrivedEventHandler"(self::"My_MsgArrivedEventCallback") ) as type "MsgArrivedEventHandler" invoke self::"add_MsgArrivedEvent" (new "MsgArrivedEventHandler"(self::"My_MsgArrivedEventCallback")) invoke MsgArrivedEvent::"Invoke"("Test message 2") end method main. method-id. My_MsgArrivedEventCallback. procedure division using by value str as string. display str end method My_MsgArrivedEventCallback. end static. end class a.See demo program |
Enumb.cbl
$set sourceformat(free) preservecase enum-id. Action. 78 #Start. *> Start is a reserved word 78 #Stop. 78 #Rewind. 78 #Forward. end enum Action. enum-id. Stat as "Status". 78 Flunk value 50. 78 Pass value 70. 78 Excel value 90. end enum Stat. program-id. main. display type "Status"::"Pass" as binary-long *> prints 70 display type "Status"::"Pass" *> prints Pass end program main.Return To Table
Choices.cbl
$set sourceformat(free) program-id. a. 01 age binary-long. 01 greeting string. 01 x binary-long. 01 y binary-long. 01 color string value "blue". 01 r binary-long value 0. 01 b binary-long value 0. 01 g binary-long value 0. 01 other-color binary-long value 0. if age < 20 move "What's up?" to greeting else move "Hello" to greeting end-if if x not = 100 and y < 5 multiply 5 by x multiply 2 by y end-if evaluate x when > 5 multiply y by x when 5 add y to x when < 10 subtract y from x when other divide y into x end-evaluate evaluate color *> can be any type when "pink" when "red" add 1 to r when "blue" add 1 to b when "green" add 1 to g when other add 1 to other-color end-evaluateReturn To Table
Loops.cbl
$set sourceformat(free) 01 c binary-long value 0. 01 names string occurs any. 01 s string. 01 i binary-long value 0. *>Pre-test loops: perform until c >= 10 *> No WHILE keyword add 1 to c end-perform perform varying c from 2 by 2 until c > 10 display c end-perform *> Post-test loops: perform with test after until c >= 10 add 1 to c end-perform *>Array or collection looping set content of names to ("Fred" "Sue" "Barney") perform varying s through names display s end-perform *>Breaking out of loops: perform until false if i = 5 exit perform end-if display i add 1 to i end-perform *>Continue to next iteration: perform varying i from 0 by 1 until i >= 5 if i < 4 exit perform cycle end-if display i end-performReturn To Table
Arrays.cbl
$set sourceformat(free) $set ilusing"System" 01 nums binary-long occurs any values 1, 2, 3. 01 names string occurs 5. *> 5 is the size of the array *> Can also do: *>01 names string occurs any. 01 names2 string occurs 7. 01 twoD float-short occurs any, any. 01 jagged binary-long occurs any, occurs any. 01 rows binary-long value 3. 01 cols binary-long value 10. set content of nums to (1 2 3 4) *> Resets the contents of the array (optionally chaning the size set size of names to 5 *> Create an array lf length 5 set names(1) to "David" *> first element indexed as 1 *>set names(6) to "Bobby" *> throws System.IndexOutOfRangeException *> COBOL cannot directly resize an array - use copy invoke type "Array"::"Copy"(names, names2, names::"Length") *> or else: invoke names::"CopyTo"(names2, 0) set size of twoD to rows, cols set size of jagged to 3 set size of jagged(1) to 5 set jagged(1 5) to 5Return To Table
Functions-a.cbl
$set sourceformat(free) preservecase class-id. a. static. method-id. main. 01 a binary-long value 1. 01 b binary-long value 1. 01 c binary-long. *> c doesn't need initializing 01 total binary-long. invoke self::"TestFunc"(a b c) *> or invoke self::"TestFunc"(value a reference b output c) display a space b space c set total to function sum(4 3 2 1) *> returns 10 invoke self::"SayHello"("Robert" "Mr.") invoke self::"SayHello"("Robert") end method main. method-id. TestFunc. procedure division using by value x as binary-long, by reference y as binary-long, output z as binary-long. add 1 to x, y move 5 to z end method TestFunc. *> COBOL doesn't support optional arguments/parameters. *> Just create two different versions of the same function. method-id. SayHello. procedure division using by value nam as string, prefix as string. display "Greetings, " prefix space nam end method SayHello. method-id. SayHello. procedure division using by value nam as string. invoke self::"SayHello"(nam "") end method SayHello. end static. end class a.Return To Table
Functions-b.cbl
$set sourceformat(free) preservecase class-id. a. static. method-id. main. 01 i binary-long. set i to self::"MySum"(1 2 3 4) display i end method main. Method-id. MySum. 01 i binary-long. Procedure division using params nums as binary-long occurs any returning mysum as binary-long. Perform varying i through nums Add i to mysum End-perform Goback End method MySum. end static. end class a.Return To Table
Strings.cbl
$set sourceformat(free) $set ilusing"System" *> x"0d" *> carriage-return *> x"0a" *> line-feed *> x"09" *> tab *> "\" *> backslash *> "" *> quote *> Chars 01 letter character. 01 word character occurs any. 01 school string value "Harding" & x"09". *> String literal 01 msg string value "File is c:\temp\x.dat". 01 mascot string value "Bisons". 01 names string value "Frank,Becky,Ethan,Braden". 01 parts string occurs any. 01 dt type "DateTime" value new "DateTime"(1973, 10, 12). 01 s string. 01 x binary-long. 01 buffer type "System.Text.StringBuilder" value new "System.Text.StringBuilder"("two "). *> string concatenation set school to string::"Concat"(school, "University") *> school is "Harding (tab) University" set letter to school::"Chars"(0) *> letter is H set letter to type "Convert"::"ToChar"(65) *> letter is A set letter to 65 as character *> same thing set word to school::"ToCharArray" *>word holds Harding *>String comparison if mascot = "Bisons" *> true display "Pass" end-if if mascot::"Equals"("Bisons") *> true display "Pass" end-if if mascot::"ToUpper"::"Equals"("BISONS") *> true display "Pass" end-if if mascot::"CompareTo"("Bisons") = 0 *> true display "Pass" end-if *> String matching - no Like equivalent , use Regex *> Substring set s to mascot::"Substring"(2 3) *> s is "son" *> Replacement set s to mascot::"Replace"("sons" "nomial") *> s is "Binomial" display s *> Split set parts to names::"Split"(",") *> Date to string set s to dt::"ToString"("MMM dd, yyyy") *> Oct 12, 1973 display s *> string to int set x to type "Convert"::"ToInt32"("-5") *> x is -5 *> Mutable string invoke buffer::"Append"("three ") invoke buffer::"Insert"(0, "one ") invoke buffer::"Replace"("two" "TWO") display buffer *> Prints "one TWO three"Return To Table
Exceptions.cbl
$set sourceformat(free) $set ilusing "System" $set ilref"Microsoft.VisualBasic.dll" *> Throw an exception 01 exc type "Exception"value new "Exception"("Something is really wrong."). 01 x binary-long. 01 y binary-long. *> Catch an exception try set y to 0; divide y into x catch exc *> Argument is optional, no "When" keyword display exc::"Message" finally invoke type "Microsoft.VisualBasic.Interaction"::"Beep" end-try raise exc *> ha haReturn To Table
ClassesInterfaces.cbl
$set sourceformat(free) preservecase *> Inheritance class-id. FootballGame inherits type "Competition". end class FootballGame. *> Interface definition *>interface-id. IAlarmClock. *>end interface IAlarmClock. *> Extending an interface interface-id. IAlarmClock inherits type "IClock". end interface IAlarmClock. *> Interface implementation class-id. WristWatch implements type "IAlarmClock", type "ITimer". end class WristWatch. interface-id. IClock. end interface IClock. interface-id. ITimer. end interface ITimer. class-id. Competition. end class Competition.Return To Table
ConstructorsDestructors.cbl
$set sourceformat(free) preservecase class-id. SuperHero. 01 _powerLevel binary-long. method-id. new. procedure division. set _powerLevel to 0 end method new. method-id. new. procedure division using by value powerLevel as binary-long. set _powerLevel to powerLevel end method new. method-id. Finalize override protected. *> Destructor code to free unmanaged resources. *> Implicitly creates a Finalize method end method Finalize. end class SuperHero.Return To Table
UsingObjects.cbl
$set sourceformat(free) preservecase $set ilusing"System.IO" program-id. main. 01 hero type "SuperHero" value new "SuperHero". 01 hero2 type "SuperHero". 01 obj object. 01 reader type "StreamReader". 01 lin string. // No "With" construct set hero::"Name" to "SpamMan" set hero::"PowerLevel" to 3 invoke hero::"Defend"("Laura Jones") invoke type "SuperHero"::"Rest" *> Calling static method set hero2 to hero *> Both reference the same object set hero2::"Name" to "WormWoman" display hero::"Name" *> Prints WormWoman set hero to null *> Free the object if hero = null set hero to new "SuperHero" end-if set obj to new "SuperHero" if obj is instance of type "SuperHero" display "Is a SuperHero object." end-if *> No 'using' construct in COBOL try set reader to type "File"::"OpenText"("test.txt") perform until exit set lin to reader::"ReadLine" if lin = null exit perform end-if end-perform finally if reader not = null invoke reader::"Dispose" end-if end-try end program main. class-id. SuperHero. static. method-id. Rest. end method Rest. end static. object. 01 #Name string property. 01 PowerLevel binary-long property. method-id. Defend. procedure division using by value attacker as string. end method Defend. end object. end class SuperHero.Return To Table
Structs.cbl
$set sourceformat(free) preservecase valuetype-id. StudentRecord. object. 01 #name string public. 01 gpa float-short public. method-id. new. procedure division using by value nam as string, gpa as float-short. set #name to nam set self::"gpa" to gpa end method new. end object. end valuetype StudentRecord. class-id. a. static. method-id. main. 01 stu type "StudentRecord" value new "StudentRecord"("Bob", 3.5). 01 stu2 type "StudentRecord". procedure division. set stu2 to stu set stu2::"name" to "Sue" display stu::"name" *> Prints Bob display stu2::"name" *> Prints Sue end method main. end static. end class a.Return To Table
Properties.cbl
$set sourceformat(free) preservecase class-id. MyClass. object. 01 _size binary-long private. method-id. get property #Size. procedure division returning ret as binary-long. set ret to _size end method. method-id. set property #Size. procedure division using by value val as binary-long. if val < 0 set _size to 0 else set _size to val end-if end method. end object. end class MyClass. class-id. a. static. method-id. main. 01 foo type "MyClass" value new"MyClass". add 1 to foo::"Size" display foo::"Size" end method main. end static. end class a.Return To Table
DelegatesEvents.cbl
$set sourceformat(free) preservecase $set ilusing"System" delegate-id. MsgArrivedEventHandler. procedure division using by value messag as string. end delegate MsgArrivedEventHandler. class-id. a. static. 01 MsgArrivedEvent type "MsgArrivedEventHandler" event. *> Delegates must be used with events in C# method-id. main. set MsgArrivedEvent to type "Delegate"::"Combine"(MsgArrivedEvent, new "MsgArrivedEventHandler"(self::"My_MsgArrivedEventCallback")) as type "MsgArrivedEventHandler" invoke MsgArrivedEvent::"Invoke"("Test message") *> Throws exception if obj is null set MsgArrivedEvent to type "Delegate"::"Remove"(MsgArrivedEvent, new "MsgArrivedEventHandler"(self::"My_MsgArrivedEventCallback")) as type "MsgArrivedEventHandler" invoke self::"add_MsgArrivedEvent"(new "MsgArrivedEventHandler"(self::"My_MsgArrivedEventCallback")) invoke MsgArrivedEvent::"Invoke"("Test message 2") *> Throws exception if obj is null end method main. method-id. My_MsgArrivedEventCallback. procedure division using by value str as string. display str end method My_MsgArrivedEventCallback. end static. end class a.Return To Table
This document quotes heavily from the following (with thanks): Produced by Dr. Frank McCown, Harding University Computer Science Dept Additional COBOL information was created by Robert Sales, Micro Focus International merging and reformatted was by Alex Turner, Micro Focus International This work is licensed under a Creative Commons