Problem:
How can they accomplish this so that there will not be major code rewriting involved in order to safeguard data in a multi-threaded environment?
Resolution:
.NET multi-threading can be used in conjunction with the Visual COBOL RunUnit class in order to create separate RunUnits that run simultaneously and are automatically protected from one another.
Here is the description of the attached demo:
*----------------------------------------------------------------------------------*
* RunUnitDemo
*
* This example program demonstrates how .NET multi-threading can be used in con-
* junction with the Visual COBOL RunUnit class in order to have multiple instances
* of a COBOL legacy application running simultaneously.
* The RunUnit class allows you to add an instance of a COBOL procedural program
* to create a new rununit for it. Each program that is called by the main program
* also becomes part of the new RunUnit and is completely isolated from other
* RunUnits that are created and running.
*
* This allows you to run multiple instances of an application without the require-
* ment to add threading code to check for resource contention.
*
* This can be used in ASP.NET or WCF Web Service applications as well as a stan-
* dard console application like this demo where threading is started manually.
*
* This demo also shows how a parameter can be passed to the new thread and then
* passed on to the starting program of the RunUnit through its linkage section.
*
* This demo will create two threads, passing a string to each. Each thread will
* create a new RunUnit class and will pass the string to the Legacy Program which
* will in turn write the passed string to a new file whose name will be formed
* using the current threads number.
*----------------------------------------------------------------------------------*
program-id. Program1 as "RununitDemo.Program1".
data division.
working-storage section.
01 rununithandler type RununitDemo.RununitHandler.
procedure division.
set rununithandler to new RununitDemo.RununitHandler
invoke rununithandler::StartThreads
goback.
end program Program1.
class-id RununitDemo.RununitHandler.
working-storage section.
01 t1 type Thread.
01 t2 type Thread.
method-id StartThreads.
local-storage section.
01 passparams object.
procedure division.
set t1 to new Thread(new ParameterizedThreadStart(self::CreateRunUnits(passparams)))
set t2 to new Thread(new ParameterizedThreadStart(self::CreateRunUnits(passparams)))
set passparams to "this is thread 1"
invoke t1::Start(passparams)
set passparams to "this is thread 2"
invoke t2::Start(passparams)
invoke t1::Join *> Join causes the main thread to wait until the thread has completed.
invoke t2::Join
goback.
end method.
method-id CreateRunUnits public.
local-storage section.
01 myRunUnit type MicroFocus.COBOL.RuntimeServices.RunUnit.
procedure division using by value s1 as object.
*> Create a run unit for the called COBOL
set myRunUnit to new MicroFocus.COBOL.RuntimeServices.RunUnit
try
*> Call the COBOL
invoke myRunUnit::Call("LegacyCOBOL", s1 as string)
catch ex as type Exception
display ex::Message
finally
*> Destroy the run unit
invoke myRunUnit::StopRun
end-try
goback.
end method.
end class.
Legacy program created in RunUnit:
$set ilusing"System.Threading"
program-id. LegacyCOBOL.
file-control.
select mylog
assign to ws-filename
organization line sequential.
data division.
file section.
fd mylog.
01 logrec pic x(50).
working-storage section.
01 ws-filename.
03 filler pic x(11) value "RununitDemo".
03 ws-file-thread pic 9(5).
03 filler pic x(4) value ".log".
linkage section.
01 passparams string.
procedure division using passparams.
move type Thread::CurrentThread::ManagedThreadId
to ws-file-thread
open extend mylog
move passparams::ToString & " From Thread : " & ws-file-thread
to logrec
write logrec
close mylog
goback.