Menu

Sorting items in an array

GnuCOBOL
Jason
2022-05-23
2022-05-24
  • Jason

    Jason - 2022-05-23

    Hello COBOL experts,

    I have a question i'm sure someone can help me with.

    I have an array:

    01 ARRAY.
    05 ARRAY-ITEMS pic x(256) occurs 10 times.

    How do I go about sorting this array so the items are all in alphabetical order?

    Any advice greatly appreciated!

     

    Last edit: Jason 2022-05-23
    • Vincent (Bryan) Coen

      Read up on the SORT verb.

      On 23/05/2022 17:49, flaneur7508 wrote:

      Hello COBOL experts,

      I have a question i'm sure someone can help me with.

      I have an array:

      01 ARRAY.
      05 ARRAY-ITEMS pic x(256) occurs 10 times.**

      How do I go about sorting this array so the items are all in
      alphabetical order?

      Any advice greatly appreciated!

       
  • serge lacombe

    serge lacombe - 2022-05-23
       IDENTIFICATION DIVISION.
       PROGRAM-ID. prg.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
      *
       01  array.
           03  array-items occurs 10 pic x(256).
       01  ind pic 99.
      *
       PROCEDURE DIVISION.
    
      *
       debut.
          move "zzz" to array-items (1)
          move "aaa" to array-items (2).
          move "bbb" to array-items (3).
          move "yyy" to array-items (5).
          move "ddd" to array-items (6).
          move "ppp" to array-items (7).
          move "mmm" to array-items (8).
          move "ggg" to array-items (9).
          move "iii" to array-items (10).
          sort array-items ascending key  array-items.
          perform varying ind from 1 by 1 until ind > 10
              display array-items (ind) (1 : 3)
          end-perform.
          stop run.
    
     
  • Jason

    Jason - 2022-05-24

    That’s very useful, I thought SORT only works on file sorts.

    Although my program compiles I have a problem.

    01 KEY-GROUP-SAVED-ARRAY.
    02 KEY-GROUP-SAVED PIC X(256) OCCURS 100 TIMES.
    01 GROUP-INDEX PIC 9(3) VALUE ZERO.

    The values in KEY-GROUP-SAVED are

    KEY-GROUP-SAVED(1) = one
    KEY-GROUP-SAVED(2) = two
    KEY-GROUP-SAVED(3) = three
    KEY-GROUP-SAVED(4) = four
    KEY-GROUP-SAVED(5) = five
    KEY-GROUP-SAVED(6 to 100) = SPACES

    …….

    DISPLAY KEY-GROUP-SAVED-ARRAY LINE 1 POSITION 1.
    SORT KEY-GROUP-SAVED ON ASCENDING KEY KEY-GROUP-SAVED.
    DISPLAY KEY-GROUP-SAVED-ARRAY LINE 31 POSITION 1.
    ACCEPT INPUT-KEY.

    When I run this, the array is display as expected (i.e. one, two, three…) prior to the SORT

    After the sort, when I display the array I just get spaces. I.e. the SORT is removing the content of the array.

    I double checked in the GNUcobol docs, and the syntax appears to be correct.

    What have I broken?

    edit. So of course the first 95 elements are indeed spaces post SORT. That's my mistake! Thank you Serge & Vincent!!

     

    Last edit: Jason 2022-05-24
    • Simon Sobisch

      Simon Sobisch - 2022-05-24

      As you found out - spaces sorts less than the rest by default. To work on this you could do one of the following:

      • initialize the table keys via VALUE HIGH-VALUE
      • define a sort collation which only includes 'A' through 'Z', 'a' through 'z', '0' through '9' and use this - everything left out will be sorted as equally to high-value
      • if you know the amount of entries: add DEPENDING ON to the OCCURS - this will also speed up the SORT
       
    • Vincent (Bryan) Coen

      The trick here is to initialise the table as high-values before loading.

      You should also have a vars set to the max table size AND test against
      that value every time you increase the count, i.e.,

      add 1 to group-index
      if group-index > key-group-table-size
           do a error-procedure such as display a warning message etc.

      Now sort the table ascending. ( low to high)

      Then process the table with a check i.e.,
      perform forever
                    if key-group-saved (group-index) = high-value
                         or group-index > key-group-table-size
                                         exit perform  *> search ends
                    end-if
                    do processing for table
                         with a exit perform cycle
      end-perform

      Simple

      Vince

      On 24/05/2022 07:27, flaneur7508 wrote:

      That’s very useful, I thought SORT only works on file sorts.

      Although my program compiles I have a problem.

      01 KEY-GROUP-SAVED-ARRAY.
      02 KEY-GROUP-SAVED PIC X(256) OCCURS 100 TIMES.
      01 GROUP-INDEX PIC 9(3) VALUE ZERO.

      The values in KEY-GROUP-SAVED are

      KEY-GROUP-SAVED(1) = one
      KEY-GROUP-SAVED(2) = two
      KEY-GROUP-SAVED(3) = three
      KEY-GROUP-SAVED(4) = four
      KEY-GROUP-SAVED(5) = five
      KEY-GROUP-SAVED(6 to 100) = SPACES

      …….

      DISPLAY KEY-GROUP-SAVED-ARRAY LINE 1 POSITION 1.
      SORT KEY-GROUP-SAVED ON ASCENDING KEY KEY-GROUP-SAVED.
      DISPLAY KEY-GROUP-SAVED-ARRAY LINE 31 POSITION 1.
      ACCEPT INPUT-KEY.

      When I run this, the array is display as expected (i.e. one, two,
      three…) prior to the SORT

      After the sort, when I display the array I just get spaces. I.e. the
      SORT is removing the content of the array.

      I double checked in the GNUcobol docs, and the syntax appears to be
      correct.

      What have I broken?

       

Log in to post a comment.