home *** CD-ROM | disk | FTP | other *** search
- * MF Professional Cobol/ VS Cobol
- * ufco025.cbl - example for dynamic attribut modification
- * attribut file <testfmt.att>
- * ---------------------------
- * Format-Textattribut: 9
- * Format-Rahmenattribut: 11
- *
- * 05 fld0 PIC X(12).
- * Distanzen in Bereich <Daten>: Feldattribut: 501 Feldtyp: 503
- * 05 fld1 PIC S9999999 value 0.
- * Distanzen in Bereich <Daten>: Feldattribut: 508 Feldtyp: 510
- * 05 fld2 PIC X(40).
- * Distanzen in Bereich <Daten>: Feldattribut: 515 Feldtyp: 517
- *
- identification division.
- program-id. test.
- environment division.
- data division.
- working-storage section.
- COPY testfmt.
- COPY ufco02.
- procedure division.
- anf-section.
- anf-000.
- call "MSON"
- COPY testfm1.
- anf-001.
- * normal output
- move " output with generated attributes ! " to fld2.
- move 0 to SM.
- move 2 to FKZ.
- move 55 to RET.
- move "testfmt " to FMT.
- call "UNIF" using FKZ FMT fld0 RET SM Daten.
- anf-002.
- * change colour of field1 and field2 (ASCII 49, ASCII 50)
- move " new colour for fld0 and fld1 ! " to fld2.
- move "1" to Datr(501).
- move "2" to Datr(508)
- move 3 to FKZ.
- move 55 to RET.
- call "UNIF" using FKZ FMT fld0 RET SM Daten.
- anf-003.
- * change access of field1 and field2
- move " new access for fld0 and fld1 ! " to fld2.
- move "a" to Datr(503).
- move "a" to Datr(510)
- move 3 to FKZ.
- move 55 to RET.
- call "UNIF" using FKZ FMT fld0 RET SM Daten.
- anf-004.
- * cange attribut of text and frame (ASCII 112, ASCII 44)
- move " new colour for text and frame ! " to fld2.
- move "p" to Datr(9).
- move "," to Datr(11)
- move 2 to FKZ.
- move 55 to RET.
- call "UNIF" using FKZ FMT fld0 RET SM Daten.
- anf-009.
- call "MSOFF"
- stop run.
-