* Complex Numbers in COBOL
* What a curiosity
IDENTIFICATION DIVISION.
CLASS-ID. "Complex" Inherits SOMObject.
ENVIRONMENT DIVISION.
Configuration Section.
Repository.
CLASS SOMObject IS "SOMObject"
CLASS UserInterface IS "UserInt" .
DATA DIVISION.
Working-Storage Section.
01 Number.
05 Real pic s9(4)V9(4).
05 Image pic s9(4)V9(4).
PROCEDURE DIVISION.
IDENTIFICATION DIVISION.
METHOD-ID. "Add" .
DATA DIVISION.
Working-Storage Section.
Linkage Section.
01 Res.
05 Real pic s9(4)V9(4).
05 Image pic s9(4)V9(4).
01 Number1.
05 Real pic s9(4)V9(4).
05 Image pic s9(4)V9(4).
01 Number2.
05 Real pic s9(4)V9(4).
05 Image pic s9(4)V9(4).
PROCEDURE DIVISION Using Number1, Number2, res.
add Real of Number1 Real of Number2 giving real of Res.
add Image of Number1 Image of Number2 giving Image of Res.
END METHOD "Add" .
IDENTIFICATION DIVISION.
METHOD-ID. "Multiply" .
DATA DIVISION.
Linkage Section.
01 Res.
05 Real pic s9(4)V9(4).
05 Image pic s9(4)V9(4).
01 Number1.
05 Real pic s9(4)V9(4).
05 Image pic s9(4)V9(4).
01 Number2.
05 Real pic s9(4)V9(4).
05 Image pic s9(4)V9(4).
PROCEDURE DIVISION Using Number1, Number2, Res.
compute Real of Res = Real of Number1 * Real of Number2
- Image of Number1 * Image of Number2.
compute Image of Res = Real of Number1 * Image of Number2
+ Image of Number1 * Real of Number2.
END METHOD "Multiply".
END CLASS "Complex" .
¤ Dauer der Verarbeitung: 0.15 Sekunden
(vorverarbeitet)
¤
|
Haftungshinweis
Die Informationen auf dieser Webseite wurden
nach bestem Wissen sorgfältig zusammengestellt. Es wird jedoch weder Vollständigkeit, noch Richtigkeit,
noch Qualität der bereit gestellten Informationen zugesichert.
Bemerkung:
Die farbliche Syntaxdarstellung ist noch experimentell.
|