Content uploaded by Hongji Yang
Author content
All content in this area was uploaded by Hongji Yang on Feb 04, 2015
Content may be subject to copyright.
Using Aspect Orientation in Understanding Legacy COBOL Code
Jianjun Pu, Zhuopeng Zhang, Jian Kang, Yang Xu and Hongji Yang
Software Technology Research Laboratory
De Montfort University, Leicester, LE1 9BH, England
{jjpu, zpzhang, jkang, yangxu, hyang@dmu.ac.uk}
Abstract
Understanding and maintaining legacy COBOL systems are
still a challenging task for both academic research and industry
practice. With the development of aspect-oriented software
engineering, aspect-oriented code comprehension and
reengineering for COBOL software systems become a very
promising research direction. In this paper, context aspect and
error handling aspect, which are two most important aspects for
COBOL code understanding, are defined. Furthermore, the
approach for aspect location and operations in COBOL code is
presented. Program slicing technique is adopted to locate aspect
code from large COBOL systems. This paper reports our
experience to date on the application of aspect-oriented
program understanding in COBOL code, and more future work
will be carry out shortly.
1. Introduction
COBOL applications are widely used and long-lived
[10]. According to research firm Gartner, there are
roughly 30 billion COBOL transactions processed every
day. The expensive issues include the expense associated
with running these systems. IBM admits that at least $1.5
trillion has been spent by enterprises to create
COBOL/CICS applications [2], and the expense
associated with maintaining those applications is
increasing rather than decreasing. COBOL applications
often run in critical areas of business. For instance, over
95% of finance–insurance data is processed with COBOL.
The serious financial and legal consequences that can
result from an application failure are one reason for the
panic over the software problems.
Aspect-Oriented Programming (AOP) has been
proposed as a technique for improving the separation of
concerns in software design and implementation. The
field of AOP has focused primarily on problem analysis,
language design, and implementation. However, aspect
orientation is applied in understanding COBOL code in
our approach by defining the context aspect and error
handling aspect. The approach to understanding legacy
COBOL cod e from aspect orientation point of view is
presented in this paper, which is organised as follows.
Section 2 describes the process to abstract COBOL code
to class diagrams, which is the representation for further
aspect-oriented understanding. Section 3 defines the
context aspect and related operations. Furthermore,
section 4 defines the error handling aspect and the
identification of error handling aspect. Section 5 presents
a case study to demonstrate our approach. Section 6
presents some related work. Finally, Section 7 concludes
the paper with a summary of our experience to date.
2. Abstraction of COBOL Code
UML class diagram is adopted to represent legacy
COBOL code. This abstraction of COBOL code makes it
easier to define the context aspect and error handling
aspect. The approach to abstract COBOL code to class
diagram representation is divided into the following steps.
2.1 Dividing Calls into Four Groups
One pr ogram PPs calling another program PPt is
indicated as PPs >>PPt. One program PPs not calling
another program PPt is indicated as PPs ≯≯ PPt. One
progr am PPs called by another program PPt is indicated as
PPs << PPt. One program PPs not called by another
progr am PPt is indicated as PPs ≮≮ PPt.
Definition 1 For one program P, its procedures and its
functions PPi, i≥0, let PP(P) be the procedure and function
set of program P, which is indicated as PP(P)={ PPi| PPi
<< P, i≥0}. PPn is called root program element if and
only if (∀ PPi∈PP(P) ⇒ (PPn >>PPi ) ) AND
(∀ PPj∈PP(P) ⇒ (PPn ≮≮ PPj ))
PPn is called leaf program element if and only if
(∀ PPi∈PP(P) ⇒ (PPn ≯≯ PPi )) AND
(∃PPj∈PP(P) ⇒ (PPn << PPi ))
PPn is called node program element if and only if
(∃PPi∈PP(P) ⇒ (PPn >> PPi )) AND
(∃PPj∈PP(P) ⇒ (PPn << PPi ))
PPn is called isolated program element if and only if
(∀ PPi∈PP(P) ⇒ (PPn ≯≯ PPi )) AND
(∀PPj∈PP(P) ⇒ (PPn ≮≮ PPi ))
31st Annual International Computer Software and Applications Conference(COMPSAC 2007)
0-7695-2870-8/07 $25.00 © 2007
In order to understand the source code as a whole, it is
necessary to describe the calling or called relationships of
those procedures in program P.
Definition 2 Procedure graph is one graph to describe
the calling or called relationships of those procedures in
program P, indicated PG. It is composed of nodes and
lines. The sequence of procedure graph PG is upper-to-
bottom. The procedure the first node represents calls the
procedures the next nodes represent. The sequence of the
next nodes is the sequence being called in the first
procedure.
Definition 3 The procedure layer is one number that
represents the depth of one procedure calling other
procedures, indicated PL(P). The procedure layer of leaf
progr am elements is 0, the procedure layer of the program
elements that only call leaf program elements is 1, the
procedure layer of program elements that call the program
elements the maximum of whose procedure layers is 2.
Let PP1, PP2, PP3 be three procedures, and assume that
PP1 is one leaf program element,
(PP2 >> PP1) AND (PP2≯≯PPi), i≥3,
(PP3>>PP1) AND (PP3>>PP2 )
AND (PP3≯≯PPi), i>3,
then PL(PP1)=0, PL(PP2)=1, PL(PP3)=2.
2.2 Generating Pseudo Classes
Definition 4 For one leaf program element P, PV is its
variable set and POP is its operation set. If PV=ф, then
P is called empty program element. That empty program
element is regarded as one class, indicated CLASS
Procedure-Name-Empty.
Figure 1. One example of class diagram
The operations in empty program element are
transferred into the attributes and operations of that class.
For one leaf program element P, its slicing criterion
Ci=<p, Vi>, 1≤i≤n, and th e corresponding slicing program
Sci, PC is the slicing criterion set PC={ Ci }, PCV is the
set of slicing criterion variables PCV(P)={ Vi }.
For the first slicing criterion C1=<p, V1>, and its slice
Sc1, PCV(Sc1) is composed of the variables of the slicing
progr am Sc1. Let V1 be the first pseudo class, PCV(Sc1) is
its attributes, POP(Sc1) is the operations of that pseudo
class. Let V2 be the second variable, and V2∈ (PCV(P)-
PCV(Sc1)). For the slicing criterion C2=<p, V2>, its slice
Sc2 and the variable set PCV(Sc2) are acquired. Let V2 be
the second pseudo class, PCV(Sc2) is its attributes, the
operations in Sc2 is the operations of that pseudo class.
The iteration goes on until (PCV(P)- ∑ PCV(Sci))=ф.
Then all the pseudo classes of all the leaf program
elements of program P are acquired.
After acquiring all the classes of leaf program
elements, node program elements of program P need to be
analysed. Because one leaf program element is one
functional module and it is called in the node program
elements, it is defined as one class in analysing node
program elements that call the leaf program element.
Definition 5 For one leaf program element P, leaf
class is the class with respect to that leaf program element
in analysing the procedures and the functions calling it,
indicated CLASS Procedure-Name-Leaf.
Assume that P is a procedure being sliced and Q is a
procedure which is called at statement i in P. The
algorithm of inter-procedural slicing CC extended from P
to Q is: CC=<n1Q, ROUT(i)f→A ∩SCOPEQ>
where n1Q is the last statement of Q, f→A means that
the actual parameters will be replaced by formal
parameters. SCOPEQ represents all variables which are
accessible in procedure Q.
ROUT(i) =∪RINC(j), where j∈IMS(i).
Assume that the source code has the procedure layer
j=n0, Cji represents the ith slicing of the jth layer, and Pj is
the procedure whose procedure layer is j. The algorithm
computes the pseudo classes which is not empty.
2.3 Generating Real Classes
Pseudo class Vji is slicing-dependent on PCV(Scji).
Every pseudo class is one group.
It is necessary to check the validity of the classes and
corresponding operations and attributes. If one class is
contained in another class, the former class is redundant
for the latter.
Definition 6 For one class Vjs, if ∃t≠s, ⇒
(PCV(Scjs) ⊆ PCV(Scjt)) AND (POV(Scjs) ⊆ POV(Scjt))
then Vjs is called otiose class. If one otiose class is not
leaf class, it is deleted. Then the real classes are
generated.
2.4 Defining Relationships among Classes
An association shows a relationship between two or
more classes. Associations have several properties:
• A name that is used to describe the association
between the two classes. Association names are
optional and need not be unique globally.
• A role at each end that identifies the function of each
class with respect to the associations.
• A cardinality at each end that identifies the possible
number of instances.
31st Annual International Computer Software and Applications Conference(COMPSAC 2007)
0-7695-2870-8/07 $25.00 © 2007
It is necessary to model generalization relationships
between objects. Generalization is used to eliminate
redundancy from the analysis model. If two or more
classes share attributes or behaviour, the similarities are
consolidated into a superclass.
2.5 Pretty Printing Class Diagrams
Consistency of attributes, operations, parameters, and
their orders of classes is essential. The realization of an
interface is performed by the implementation of
operations and attributes of a class or a component.
Inheritance is modelled vertically and other
relationships horizontally. If two classes interact with
each other, some kind of relationship may be needed
between them. The transitory relationship is a
dependency. In class diagrams, multiplicity between
classes is essential and necessary and usually the
multiplicity “*” can be replaced by “1..*” or “0..*”. An
aggregation is a specification of association that depict a
whole-part relationship.
3. Context Aspect
3.1 Definition of Context Aspect
Context aspect of legacy COBOL code is the
environmental description that introduces the COBOL
type [8], the explanation in source code with the notes,
and SQL functions. It is presented with UML class
diagram that contains three classes: Type COBOL Class,
Notes Class, and SQL Class.
3.2 Type COBOL Class
Definition 7 Class of Type COBOL is the class that
represents the type of COBOL used in programming. Its
name is Type Name, its attribute is the production
corporation, and its operation is the extended
functionality.
Table 1. Type COBOL class
Class-Name: Type Name
Attribute: Production Corporation
Operation: Extended Functionality
3.3 Note Class
In COBOL code, the notes are useful for explaining
the ideas of programming, the structure of pr ogram, the
precondition of executing statements, the strategy of
controlling process, and etc. They are not executable.
They describe directly the information for understanding
the code and executing what should be done [5].
* I nitialise the variables for the get call
MO VE MQGMO-SYNCPOINT TO MQGMO-OPTIONS.
ADD MQGMO-NO-WAIT TO MQGMO-OPTIONS.
MO VE VD3-MSGID TO MQMD -MSGID.
MO VE VD3-CORRELID TO MQMD -CORRELID.
* G et the chosen message
CALL 'MQGET' USING VD3-HCONN
……
W01-REASON.
* I f the call fails build an error message, otherwi se
* prepar e the screen fields and display t he me ssage
IF W01-COMPCODE NOT = MQCC-OK
……
EL SE
……
END-IF.
EXEC CICS IGNORE CONDITION
MAPFAIL
END-EXEC.
……
* Display the message until the user presses PF3
……
In order to describe the notes in comprehending the
legacy COBOL code with depicting the context of
COBOL code, note class is presented. Note class of
legacy COBOL code is one function that contains the
notes of one legacy COBOL system to introduce the
structure of programs, explain the ideas of programming,
present the organization of the system, depict the
preconditions of executing statements, illustrate the
strategy of controlling process, clarify the anticipated
results of the execution in the legacy COBOL code.
Table 2. Note class
Class-Name: Note Class
Line: Line-number
Displa y: presenting description
3.4 SQL Class
SQL stands for the Structured Query Language. It is
one of the fundamental bases of modern database
architecture. SQL defines the methods used to create and
manipulate relational databases on all major platforms.
SQL takes into the programming world many flavours.
Oracle databases utilize their proprietary PL/SQL.
Microsoft SQL Server makes use of Transact-SQL.
However, all of these variations are based upon the
industry standard ANSI SQL. All modern relational
databases, including Access, FileMaker Pro, Microsoft
SQL Server and Oracle regard SQL as their basics. In
fact, it’s often the only way that can be truly interacted
with the database.
Table 3. SQL Command example
Keyword pair One Example
EXEC SQL
Statement string
Any valid SQL statement
Statement terminator
END-EXEC.
EXEC SQL DE LETE FROM HOTE L END-EXEC .
IF SQLS TATE NOT = "02000" THEN
EXEC SQL COMMIT END-EXEC
ELSE
EXEC SQL ROLLBACK END-EXEC
SQL can be used in COBOL programming [13]. SQL
statements are identified by the leading delimiter EXEC
SQL and terminated by END-EXEC. SQL statements are
treated exactly as ordinary COBOL statements with
regard to the use of an ending period to mark the end of a
31st Annual International Computer Software and Applications Conference(COMPSAC 2007)
0-7695-2870-8/07 $25.00 © 2007
COBOL sentence. Any valid COBOL punctuation may be
placed after the END-EXEC terminator.
Host variables used in SQL statements must be
declared within the SQL DECLARE SECTION,
delimited by the statements BEGIN DECLARE
SECTION and END DECLARE SECTION. Host
variables follow the same scope rules as ordinary
variables in COBOL. SQL descriptor names, cursor
names and statement names must be unique within the
compilation unit. A compilation unit for COBOL is the
same as a routine.
Table 4. SQL class
Class-Name: SQL COBOL
Organi sation: ANSI
Operation: EXEC SQL… END- EXEC
SQL is very simple and helpful in COBOL
programming. SQL has a limited number of commands
and those commands are very readable and easy to
understand.
Figure 2. Class diagram of context hardware
4 Error Handling Aspect
4.1 Definition of Error Handling Aspect
An error is an event that occurs during the execution
of a program that disrupts the normal flow of instructions
during the execution of a program. The error is a
condition dealing with unusual states that changes the
normal flow of control in a program. One error in the
progr am may be raised by hardware or software.
The runtime system searches the paragraph for a
method that contains a block of code that can handle the
error. This block of code is called an error handler. The
process and the techniques of coping with the errors in the
software system are called error handling.
An exception in the program is any unusual event,
erroneous or not, that is detectable by the hardware or
software and that may require special processing. An
exception is generated when the associated event occurs.
The special processing is called exception handling. The
code unit that does it is called an exception handler.
4.2 Identifying Error Handling Aspect
4.2.1 Candidates of Error Handling
When the program executes its main task, it is
conventional to detect the correctness of input and output,
the validity of the execution, and the coincidence of the
comparison. Only if the error is checked out, the step to
cope with the error is performed. Therefore the detection
is the first thing of error handling.
Table 5. Example of error handling aspect
Normal STOP IDENTIFICATION DIVISION.
PROGRAM-ID. ExampleProgram.
……
PROCEDURE DIVISION.
……
DisplayInformation.
DISPLAY "I did it".
……
STOP RUN.
Discussed Case1 ……
PROCEDURE DIVISION.
……
IF (S NOT GREATER THAN LEVEL1) AND
(NOT-ON-ORDER)
PERFORM RECORD-ERROR.
……
CLOSE FILE1, FI LE2, FILE3
STOP RUN.
……
END-IF
……
Discussed Case2 PROCEDURE DIVISION.
……
PERFORM UN TIL END-OF-FILE
……
IF NOT-ON-ORDER
……
PERFORM RECORD-ERRORS
S TOP RUN.
…….
END-IF
……
CLOSE STOCK-FILE, ORDER-FILE.
……
END-PERFORM.
……
COBOL utilises conditional operations, which
indicated as SCD, VERB(SCD)={ IF, IF…ELSE…,
EVALUATE, PERFORM…UNTIL (BY)…,
CONTINUE, SEARCH } to execute detection tasks. So
the set SCD(P) is the candidate of error handling in
progr am P. The discussion below are based on the
Weiser’s theorem [3], [14].
Theorem 1 Let i be one node of program P. The node
i is one candidate of error handling case if
ND(i) ≠ф
4.2.2 Error Handling with Termination Keywords
After one program P fin ishes its task, it stops with
COBOL reserved words “STOPRUN”, “GOBACK”,
“EXIT PROGRAM”, or “RETURN”. Those words are
defined as Termination Key Words, indicated “STOP”.
Theorem 2 Let k0 be the node “STOP”, i be one node,
t0 be the last node of program P. One error handling case
occurs if ∃i∈P, (k0 ∈ND(i)) AND (k0 !∈DOM(t0))
That is, for one program P, one error handling case
happens when the statement STOPRUN is not on every
31st Annual International Computer Software and Applications Conference(COMPSAC 2007)
0-7695-2870-8/07 $25.00 © 2007
path to the end of program P. The program P stops with
not finishing its task. It is called abnormal termination. Its
operation set is indicated s1.
4.2.3 Error Handling with GOTO-EXIT Couple
The statements of GOTO-EXIT couple are used in the
error handling. The control body of i statement includes
GOTO statement, and the control of program jumps to the
EXIT-PROGRAM.
Table 6. An example of GOTO-EXIT couple
Source Code Control Flow
1. ACCEPT AA.
2. ACCEPT AB.
3. ACCEPT AC.
4. IF (AA<0) THEN
5. DISPLAY AA.
6. GO TO EXIT-
PROGRAM.
7. END-IF
8. ADD AA TO AB.
9. ADD AB TO AC.
10. DISPLAY AC.
11. EXIT-PROGRAM:
12. EXIT
Theorem.3 Let k0 be the node “GOTO jump-name”,
s0 be the node “jump-name”, t0 be the last node of
program P. Assume that i is one node of P. One error
handling case occurs if
∃i∈P, (k0 ∈ND(i)) AND(s0∈DOM(t0)) AND
(k0 !∈DOM(t0))
That is, when one error occurs in program P satisfying
one condition in the statement i, the control flow jumps to
the flow of the exit of the program P. Its operation set is
indicated s2.
Table 7. Typical mode of error handling
BEGIN
INPUT data
<INPUT-ERROR>
<DO input-error-handling>
PERFORM data1
<PERFORM-ERROR1>
<DO perform-error-handling1>
…
PERFORM datan
<PERFORM-ERRORn>
<DO perform-error-handlingn>
OUtPUT data
<OUTPUT-ERROR>
<DO output-error-handling>
END
For the example in the Table 6:
k0 =6; s0 =11; t0 =12; i=4;
ND(i)={5,6,8,9,10}; DOM(t0)={1,2,3,4,11,12}.
k0 ∈ND(i);
s0∈DOM(t0);
k0 !∈DOM(t0).
Therefore, the set {5, 6} is the error handling part in
the example program.
4.2.4 The Rest of Error Handling
The rest candidates of error handling aspects in P is
indicated s3: s3=SCD(P)-s1-s2
The error handling is unusual event of processing, and
it does not realize the main function of the program
except the error handling program. It detects the
preconditions in the program and executes special
processing. The rest of error handling is extracted with the
typical mode of error handling from the rest candidates of
error handling in P indicated s3.
Table 8. Source code-putting message program
1 PROCESS-INQUIRYQ-MESSAGE SECTION.
2 IF NOT INITIAL-INQUIR Y-MES SAGE
3 M OVE W06-CALL-ERROR TO W06-CALL-STATUS
4 GO TO PROCESS-INQUIR YQ -MESSAGE-EXIT
5 END -IF.
6 MOV E LENGTHOFCSQ4BIIM-MSG TO W03-BUFFLEN.
7 COMP UTE MQPMO-OPTIONS = MQPMO-SYNCPOINT +
8 MQP MO-PASS-IDENTITY-CON TEXT.
9 MOV E W03-HOBJ-INQUIRYQ TO MQPMO-CON TEXT.
10 CALL 'MQPUT' USING W03-HCONN
11 W03-HOBJ-W AITQ
12 IF W 03-COMPCODE NOT = MQCC-OK
13 MOVE 'MQPUT' TO M02-OP ERATION
14 MOVE W06-CALL-ERROR TO W06-CALL-STA TUS
15 GO TO PROCESS-INQ UIR YQ-MESSAGE-EXIT
16 END- IF.
17 SE T ACCOUNT-Q UERY-MESSAGE TO TRUE.
18 MOVE SPAC ES TO CSQ4BCAQ-CHARGING.
19 MOVE LENG TH OF CSQ4BCAQ-MSG TO W03-BUFFLEN.
20 COMP UTE MQPMO-OPTIONS = MQPMO-SYNCPOINT +
21 MQPMO-PASS-IDEN TITY-
CONTEXT.
22 MOVE W03-HOBJ-INQUIRYQ TO MQPMO-CONTEXT.
23 CALL 'MQP UT' USING W03-HCONN
24 W03-HOBJ-C HECKQ
25 IF W 03-COMPCODE NOT = MQC C-OK
26 MOVE 'MQPUT' TO M02-OPERATION
27 MOVE W06-CALL-ERROR TO W06-C ALL-STATUS
28 GO TO PROCESS-INQ UIR YQ-MESSAGE-EXIT
29 END- IF.
30 MOVE CS Q4BIIM-LOANREQ TO W01-AMOUNT
31 MOVE MQMI-NONE TO MQMD-MSGID
32 MOVE LENG TH OF CSQ4BCAQ-MSG TO W03-BUFFLEN
33 COMP UTE MQPMO-OPTIONS = MQPMO-SYNCPOINT +
34 MQPMO-PASS-IDENTITY-CON TEXT
35 M OVE W03-HOBJ-INQUIRYQ TO MQPMO-CONTEXT
36 CALL 'M QPUT' USING W03-HCONN
37 W03-HO BJ-DISTQ
38 END-CALL
39 IF W03-COMPCODE NOT = MQC C-OK
40 MOVE 'MQPUT ' TO M02-OP ERATION
41 MOVE W06-CALL-ERROR TO W06-CALL-STATUS
42 END-IF.
43 PROCESS-INQUIRYQ-MESSAGE-EXI T.
44 EXIT.
45 EJECT
5. Case Study
One COBOL source code, which is named as Putting
Message Program, is presented in Table 8. It is to put one
message into the queue written in COBOL 1985. Because
it has not notes, therefore its note class is null in context
aspect. Because
ND(2) = {3, 4, 6, ,7, 9, 10} ≠ф
ND(12) = {13, 14, 15, ,17, 18, 19, 20, 22, 23} ≠ф
ND(25) = {26, 27, 28, 30, 31, 36} ≠ф
ND(39) = {40, 41} ≠ф,
the candidates set of the nodes of error handling in the
progr am is (ND(2) ∪ ND(12) ∪ ND(25) ∪ ND(39)).
Under the guidance of Theorem 3, the node set of error
handling is {3, 4, 13, 14, 15, 26, 27, 28, 40, 41}.
31st Annual International Computer Software and Applications Conference(COMPSAC 2007)
0-7695-2870-8/07 $25.00 © 2007
Figure 3. Generated context aspect
6. Related Work
Because legacy COBOL systems still play an
important role in business, a lot of research work has been
done to maintain these software systems. [12] presents an
approach to modelling legacy COBOL code with UML
collaboration diagrams via a Wide Spectrum Language.
[9] reviews the basic postulates of structured
progr amming as applied to COBOL, and discusses the
mechanical transformations archived by an automated
restructuring tool. 0 provides a tool taxonomy list which
covers more than 100 tools available for working with
COBOL. [11] presents an approach to modelling legacy
COBOL systems via UML class diagrams and use case
diagrams according to the acquisition of domain
knowledge.
Fig. 4. Control flow of putting message program
The research of combining AOP and code
comprehension is performed in different context. [15]
presents techniques to construct control-flow
representations for aspect-oriented programs, and discuss
some applications of the representations in a program
comprehension and maintenance environment. [6]
proposes several specific techniques such as aspect-
orientation or separation of concerns and product maps to
assist different RE activities. [3] points out that some
asser tions tend to be crosscutting and proposes a
modularisation of such assertion with aspect-oriented
language. [7] studies AOP in the context of business
progr amming with COBOL and discusses a pr ototypical
implementation of AspectCobol.
7. Conclusions
The approach described in this paper utilises Aspect
Orientation to realise the context aspect and error
handling aspect in order to better comprehending the
legacy COBOL code. Context aspect of legacy COBOL
code is presented with UML class diagram. The
candidates of error handling aspects are distilled from
COBOL code, and then the error handling aspect is
derived with the IF-STOPRUN couple, GOTO-EXIT
couple, the typical mode. Context aspect and error
handling aspect are greatly helpful for the comprehension
and reuse of legacy COBOL code.
References
[1] E. C. Arranga, ‘‘Cobol tools: overview and taxonomy,’’
IEEE
Software
, 17(2), 2000, pp. 59-69.
[2] IBM,
User’s Guide: COBOL and CICS Command Level
Conversion Aid for OS/390 & MVS & VM
, Version 2, IBM,
2002.
[3] T. Ishio, T. Kamiya, S. Kusumoto and K. Inoue, ‘‘Aspect-oriented
modularization of assertion crosscutting objects,’’ In
Proc. 12th
Asia-Pacific Software Engineering Conf.
, 2005.
[4] J. Jiang, X. Zhou and D. J. Robson,
‘‘
Program slicing for C -- the
problems in implementation,’’ In
Proc. IEEE Int’l Conf. Software
Maintenance
, 1991, pp. 182-190.
[5] C. Jones,
COBOL Programming Course
, available online at
http://www.csis.ul.ie/COBOL/Course/capers, 1999.
[6] C. Kuloor and A. Eberlein , ‘‘Aspect-oriented requirements
engineering for software product lines,’’ In
Proc.10th IEEE Int’l
Conf. and Workshop on the Engineering of Computer-Based
Systems
, 2003, pp. 98-107.
[7] R. Lammel and K. De Schutter, ‘‘What does aspect-oriented
programming mean to Cobol?,’’ In
Proc. 4th Int’l Conf. on
Aspect-Oriented Software Development
, 2005, pp. 99-110.
[8] Liant Software Corporation,
RM/COBOL User’s Guide
,
Version
7.5 for UNIX and Windows,
Liant Software Corporation, 2003.
[9] J. C. Mi ller and B. M. Strauss, ‘‘Implications of automated
restructuring of COBOL,’’
SIGPLAN Notices
, 1987, pp. 76 --- 82.
[10] M. Morach, ‘‘The present and future for past languages --- Cobol,’’
Database and Network Journal
, 35(1), 2005, pp. 18-19.
[11] J. Pu, R. Millham and H. Yang, ‘‘Acquiring domain knowledge in
reverse engineering legacy code into UML,’’ In
Proc. Int’l Conf.
Software Engineering and Applications
, 2003, pp. 488-493.
[12] J. Pu, Z. Zhang, Y. Xu and H. Yang, ‘‘Reusing legacy COBOL
code with UML collaboration diagrams via a wide spectrum
language,’’ In
Proc. IEEE Int’l Conf. on Information Reuse and
Integration
, 2005, pp 78-83.
[13] N. Stern and R. A. Stern, ‘‘Structured COBOL Programming --
Getting Started with Fujitsu COBOL Update’’, John Wiley &
Sons Inc., 2000.
[14] M. Weiser, ‘‘Program slicing,’’
IEEE Transactions on Software
Engineering
, 10(4), 1984, pp. 352---357.
[15] J. Zhao, ‘‘Control-flow analysis and representation for aspect-
oriented programs,’’ In
Proc. 6th Int’l Conf. on Quality Software
,
2006, pp. 277-281.
31st Annual International Computer Software and Applications Conference(COMPSAC 2007)
0-7695-2870-8/07 $25.00 © 2007