Skip to main content

Hello,

how is the SCROLL Phrase used?
http://supportline.microfocus.com/Documentation/AcucorpProducts/docs/v6_online_doc/gtman3/gt3664.htm

my tests:

  • modify main-screen scroll up by 1
  • modify main-screen scroll up by 1 line
  • modfiy main-window scroll up by 1
  • modify main-window scroll up by 1 line

then i read the description again...
Scrolling is the first operation performed by the ACCEPT or DISPLAY statement

so i thought i have to use it with display.

  • display main-screen scroll up by 1
  • display main-screen scroll up by 1 line 

but this also don't work... again compiler errors...

Can anyone help?

David

 

Hello,

how is the SCROLL Phrase used?
http://supportline.microfocus.com/Documentation/AcucorpProducts/docs/v6_online_doc/gtman3/gt3664.htm

my tests:

  • modify main-screen scroll up by 1
  • modify main-screen scroll up by 1 line
  • modfiy main-window scroll up by 1
  • modify main-window scroll up by 1 line

then i read the description again...
Scrolling is the first operation performed by the ACCEPT or DISPLAY statement

so i thought i have to use it with display.

  • display main-screen scroll up by 1
  • display main-screen scroll up by 1 line 

but this also don't work... again compiler errors...

Can anyone help?

David

 

I agree it is not obvious ... attaching a program .. the program needs to be run with the Configuration variable SCROLL FALSE ..this phrase in the program  

          display label "line 24 info" line 24 col 5          

          accept omitted scroll down 2 lines

change the accept omitted to

          accept omitted scroll up 2 lines

and then you will see the label displayed

     *{Bench}prg-comment

     * Program7.cbl

     * Program7.cbl is generated from C:\\Project5\\Program7.Psf

     *{Bench}end

      IDENTIFICATION              DIVISION.

     *{Bench}prgid

      PROGRAM-ID. Program7.

      AUTHOR. SHjerpe.

      DATE-WRITTEN. Tuesday, June 11, 2013 10:02:50 AM.

      REMARKS.

     *{Bench}end

      ENVIRONMENT                 DIVISION.

      CONFIGURATION               SECTION.

      SPECIAL-NAMES.

     *{Bench}activex-def

     *{Bench}end

     *{Bench}decimal-point

     *{Bench}end

      INPUT-OUTPUT                SECTION.

      FILE-CONTROL.

     *{Bench}file-control

     *{Bench}end

      DATA                        DIVISION.

      FILE                        SECTION.

     *{Bench}file

     *{Bench}end

      WORKING-STORAGE             SECTION.

     *{Bench}acu-def

      COPY "acugui.def".

      COPY "acucobol.def".

      COPY "crtvars.def".

      COPY "showmsg.def".

     *{Bench}end

     *{Bench}copy-working

      77 Quit-Mode-Flag PIC S9(5) COMP-4 VALUE 0.

      77 Key-Status IS SPECIAL-NAMES CRT STATUS PIC 9(4) VALUE 0.

          88 Exit-Pushed VALUE 27.

          88 Message-Received VALUE 95.

          88 Event-Occurred VALUE 96.

          88 Screen-No-Input-Field VALUE 97.

          88 Screen-Time-Out VALUE 99.

     * property-defined variable

     * user-defined variable

      77 Form1-Handle

                 USAGE IS HANDLE OF WINDOW.

      01 ef-value         PIC  x(10).

      77 Form1-Ef-1-Value PIC  X(30).

     *{Bench}end

      LINKAGE                     SECTION.

     *{Bench}linkage

     *{Bench}end

      SCREEN                      SECTION.

     *{Bench}copy-screen

      01 Form1,

          BEFORE PROCEDURE Form1-Bef-Procedure.

          03 Form1-Ef-1, Entry-Field,

             COL 30.00, LINE 4.00, LINES 2.00 CELLS, SIZE 11.00 CELLS,

             3-D, ID IS 1, VALUE Form1-Ef-1-Value.

     *{Bench}end

     *{Bench}linkpara

      PROCEDURE DIVISION.

     *{Bench}end

     *{Bench}declarative

     *{Bench}end

      Acu-Main-Logic.

     *{Bench}entry-befprg

     *    Before-Program

     *{Bench}end

          PERFORM Acu-Initial-Routine

     * run main screen

     *{Bench}run-mainscr

          PERFORM Acu-Form1-Routine

     *{Bench}end

          PERFORM Acu-Exit-Rtn

          .

     *{Bench}copy-procedure

      COPY "showmsg.cpy".

      Acu-Initial-Routine.

     *    Before-Init

     * get system information

          ACCEPT System-Information FROM System-Info

     * get terminal information

          ACCEPT Terminal-Abilities FROM Terminal-Info

     *    After-Init

          .

      Acu-Exit-Rtn.

     *    After-Program

          EXIT PROGRAM

          STOP RUN

          .

      Acu-Form1-Routine.

     *    Before-Routine

          PERFORM Acu-Form1-Scrn

          PERFORM Acu-Form1-Proc

     *    After-Routine

          .

      Acu-Form1-Scrn.

          PERFORM Acu-Form1-Create-Win

          PERFORM Acu-Form1-Init-Data

          .

      Acu-Form1-Create-Win.

     *    Before-Create

     * display screen

             DISPLAY Standard GRAPHICAL WINDOW

                LINES 25.00, SIZE 64.00, CELL HEIGHT 10,

                CELL WIDTH 10, AUTO-MINIMIZE, AUTO-RESIZE,

                COLOR IS 65793, LABEL-OFFSET 0, LINK TO THREAD,

                MAX-LINES 24.00, MODELESS, RESIZABLE,

                WITH SYSTEM MENU,

                TITLE "Screen", TITLE-BAR, NO WRAP,

                EVENT PROCEDURE Form1-Event-Proc,

                HANDLE IS Form1-Handle

     * toolbar

          DISPLAY Form1 UPON Form1-Handle

     *    After-Create

          .

      Acu-Form1-Init-Data.

     *    Before-Initdata

     *    After-Initdata

          .

     * Form1

      Acu-Form1-Proc.

          PERFORM UNTIL Exit-Pushed

             ACCEPT Form1  

                ON EXCEPTION PERFORM Acu-Form1-Evaluate-Func

             END-ACCEPT

          END-PERFORM

          DESTROY Form1-Handle

          INITIALIZE Key-Status

          .

     * Form1

      Acu-Form1-Evaluate-Func.

          EVALUATE TRUE

             WHEN Exit-Pushed

                PERFORM Acu-Form1-Exit

             WHEN Event-Occurred

                IF Event-Type = Cmd-Close

                   PERFORM Acu-Form1-Exit

                END-IF

          END-EVALUATE

          MOVE 1 TO Accept-Control

          .

      Acu-Form1-Exit.

          SET Exit-Pushed TO TRUE

          .

      Acu-Form1-Event-Extra.

          EVALUATE Event-Type

          WHEN Msg-Close

             PERFORM Acu-Form1-Msg-Close

          END-EVALUATE

          .

      Acu-Form1-Msg-Close.

          ACCEPT Quit-Mode-Flag FROM ENVIRONMENT "QUIT_MODE"

          IF Quit-Mode-Flag = ZERO

             PERFORM Acu-Form1-Exit

             PERFORM Acu-Exit-Rtn

          END-IF

          .

      Form1-Event-Proc.

     *

          PERFORM Acu-Form1-Event-Extra

          .

     ***   start event editor code   ***

     *

      Form1-Bef-Procedure.

          display label "line 24 info" line 24 col 5

          accept omitted scroll down 2 lines   .

     *{Bench}end

      REPORT-COMPOSER SECTION.


Hello,

how is the SCROLL Phrase used?
http://supportline.microfocus.com/Documentation/AcucorpProducts/docs/v6_online_doc/gtman3/gt3664.htm

my tests:

  • modify main-screen scroll up by 1
  • modify main-screen scroll up by 1 line
  • modfiy main-window scroll up by 1
  • modify main-window scroll up by 1 line

then i read the description again...
Scrolling is the first operation performed by the ACCEPT or DISPLAY statement

so i thought i have to use it with display.

  • display main-screen scroll up by 1
  • display main-screen scroll up by 1 line 

but this also don't work... again compiler errors...

Can anyone help?

David

 

thanks for your reply :)

but the scroll phrase didn't work for my needs... and i must find another way to handle my problem.


Hello,

how is the SCROLL Phrase used?
http://supportline.microfocus.com/Documentation/AcucorpProducts/docs/v6_online_doc/gtman3/gt3664.htm

my tests:

  • modify main-screen scroll up by 1
  • modify main-screen scroll up by 1 line
  • modfiy main-window scroll up by 1
  • modify main-window scroll up by 1 line

then i read the description again...
Scrolling is the first operation performed by the ACCEPT or DISPLAY statement

so i thought i have to use it with display.

  • display main-screen scroll up by 1
  • display main-screen scroll up by 1 line 

but this also don't work... again compiler errors...

Can anyone help?

David

 

perhaps you should post what you are trying to do .. there are a lot of developers that see this forum .. they may have some ideas