home *** CD-ROM | disk | FTP | other *** search
/ Power-Programmierung / CD1.mdf / cobol / library / cobolwi / ufco035.cbl < prev    next >
Text File  |  1993-07-28  |  2KB  |  62 lines

  1.       *  MS Cobol/ MF Cobol2
  2.       *  ufco035.cbl - example for dynamic attribut modification
  3.       *  attribut file <testfmt.att>
  4.       *  ---------------------------
  5.       *  Format-Textattribut:    9
  6.       *  Format-Rahmenattribut: 11
  7.       *
  8.       *   05 fld0                   PIC X(12).
  9.       *   Distanzen in Bereich <Daten>:   Feldattribut: 501    Feldtyp: 503
  10.       *   05 fld1                   PIC S9999999 value 0.
  11.       *   Distanzen in Bereich <Daten>:   Feldattribut: 508    Feldtyp: 510
  12.       *   05 fld2                   PIC X(40).
  13.       *   Distanzen in Bereich <Daten>:   Feldattribut: 515    Feldtyp: 517
  14.       *
  15.        identification division.
  16.        program-id. ufco035.
  17.        environment division.
  18.        data division.
  19.        working-storage section.
  20.            COPY testfmt.
  21.            COPY ufco03.
  22.        procedure division.
  23.        anf-section.
  24.        anf-000.
  25.        call "MOUSEON"
  26.            COPY testfm1.
  27.        anf-001.
  28.       * normal output
  29.        move " output with generated attributes !     " to fld2.
  30.        move 0 to SM.
  31.        move 2 to FKZ.
  32.        move 55 to RET.
  33.            move "testfmt " to FMT.
  34.            call "UNIF" using FKZ FMT fld0 RET SM Daten.
  35.        anf-002.
  36.       * change colour of field1 and field2 (ASCII 15, ASCII 7)
  37.        move " new colour for fld0 and fld1 !         " to fld2.
  38.        move "" to Datr(501).
  39.        move "" to Datr(508)
  40.        move 3 to FKZ.
  41.        move 55 to RET.
  42.        call "UNIF" using FKZ FMT fld0 RET SM Daten.
  43.        anf-003.
  44.       * change access of field1 and field2
  45.        move " new access for fld0 and fld1 !         " to fld2.
  46.        move "a" to Datr(503).
  47.        move "a" to Datr(510)
  48.        move 3 to FKZ.
  49.        move 55 to RET.
  50.        call "UNIF" using FKZ FMT fld0 RET SM Daten.
  51.        anf-004.
  52.       * cange attribut of text and frame (ASCII 112, ASCII 44)
  53.        move " new colour for text and frame !        " to fld2.
  54.        move "p" to Datr(9).
  55.        move "," to Datr(11)
  56.        move 2 to FKZ.
  57.        move 55 to RET.
  58.        call "UNIF" using FKZ FMT fld0 RET SM Daten.
  59.        anf-009.
  60.        call "MOUSEOFF"
  61.            stop run.
  62.