Hubert Hackin''
  • All posts
  • About
  • Our CTF

NSEC21 The Cabal - Sun, Jun 6, 2021 - Barberousse

| Rev Cobol | Nsec21

The Cabal

This challenge takes us back to a time long ago, almost as far as the medieval times of this year’s theme, the 60’s!

We are provided with a challenge.cabal file which turns out to be EBCDIC encoded text. EBCDIC is a character encoding (like ASCII) that was mainly used on IBM mainframes.

Converting it to something usable

$ file challenge.cabal
challenge.cabal: EBCDIC text

Being under 50, this is the first time we’ve encountered this. Luckily, there are tools to convert this to ASCII encoding; we used good old dd.

$ dd if=challenge.cabal of=challenge_ascii.cabal conv=ascii

Which gives us the following source code.

IDENTIFICATION DIVISION.
PROGRAM-ID. GET-FLAG.

DATA DIVISION.
WORKING-STORAGE SECTION.
78 KEY-LEN          VALUE   28.
78 ANSWER-OF-LIFE   VALUE   42.
01 CHAR-INDEX       PIC     99.
01 USER-KEY         PIC     X(KEY-LEN).
01 KEY-TABLE.
   05 KEY-VALUE    PIC     X(09)    OCCURS KEY-LEN TIMES.
01 IS-VALID         PIC     9(5)     COMP.
01 ARG1             PIC     9(5)     COMP.
01 ARG2             PIC     9(5)     COMP.
01 RETRN            PIC     9(5)     COMP.
01 RSD1             PIC     9(5)     COMP.
01 RSD2             PIC     9(5)     COMP.
01 QTN1             PIC     9(5)     COMP.
01 QTN2             PIC     9(5)     COMP.
01 BIT-VAL          PIC     9(5)     COMP.


PROCEDURE DIVISION.
000-MAIN.
   DISPLAY "PLEASE ENTER THE KEY ("KEY-LEN" chars)".
   ACCEPT USER-KEY.
   PERFORM 001-SET-FLAG-KEY.
   MOVE 1 TO IS-VALID
   MOVE 1 TO CHAR-INDEX.
   PERFORM UNTIL CHAR-INDEX > KEY-LEN
	   COMPUTE ARG1 = FUNCTION ORD(USER-KEY(CHAR-INDEX:1)) - 1
	   MOVE KEY-VALUE(CHAR-INDEX) TO ARG2
	   PERFORM 002-MAGIC-OP
	   IF RETRN IS NOT EQUAL TO ANSWER-OF-LIFE
		  MOVE 0 TO IS-VALID
		END-IF
	   ADD 1 TO CHAR-INDEX
   END-PERFORM.
   IF IS-VALID IS EQUAL TO 1
	  DISPLAY "VALID KEY ENTERED. WELCOME TO THE CABAL."
  ELSE
	  DISPLAY "INVALID KEY ENTERED."
  END-IF.
   STOP RUN.

001-SET-FLAG-KEY.
   MOVE 108 TO KEY-VALUE(1).
   MOVE 102 TO KEY-VALUE(2).
   MOVE 107 TO KEY-VALUE(3).
   MOVE 109 TO KEY-VALUE(4).
   MOVE 7 TO KEY-VALUE(5).
   MOVE 105 TO KEY-VALUE(6).
   MOVE 101 TO KEY-VALUE(7).
   MOVE 104 TO KEY-VALUE(8).
   MOVE 101 TO KEY-VALUE(9).
   MOVE 102 TO KEY-VALUE(10).
   MOVE 27 TO KEY-VALUE(11).
   MOVE 121 TO KEY-VALUE(12).
   MOVE 126 TO KEY-VALUE(13).
   MOVE 98 TO KEY-VALUE(14).
   MOVE 111 TO KEY-VALUE(15).
   MOVE 105 TO KEY-VALUE(16).
   MOVE 107 TO KEY-VALUE(17).
   MOVE 104 TO KEY-VALUE(18).
   MOVE 107 TO KEY-VALUE(19).
   MOVE 102 TO KEY-VALUE(20).
   MOVE 108 TO KEY-VALUE(21).
   MOVE 106 TO KEY-VALUE(22).
   MOVE 124 TO KEY-VALUE(23).
   MOVE 101 TO KEY-VALUE(24).
   MOVE 120 TO KEY-VALUE(25).
   MOVE 99 TO KEY-VALUE(26).
   MOVE 126 TO KEY-VALUE(27).
   MOVE 25 TO KEY-VALUE(28).

002-MAGIC-OP.
   MOVE 1 TO BIT-VAL.
   MOVE ZERO TO RETRN.
   IF ARG1 IS NOT EQUAL TO ZERO OR ARG2 IS NOT EQUAL TO ZERO
	  PERFORM 003-MAGIC-OP-SUB
		UNTIL ARG1 IS EQUAL TO ZERO AND ARG2 IS EQUAL TO ZERO.

003-MAGIC-OP-SUB.
   DIVIDE ARG1 BY 2 GIVING QTN1.
   COMPUTE RSD1 = ARG1 - QTN1 * 2.
   DIVIDE ARG2 BY 2 GIVING QTN2.
   COMPUTE RSD2 = ARG2 - QTN2 * 2.
   IF RSD1 IS NOT EQUAL TO RSD2 THEN
	  ADD BIT-VAL TO RETRN
	END-IF.
   MULTIPLY BIT-VAL BY 2 GIVING BIT-VAL.
   MOVE QTN1 TO ARG1.
   MOVE QTN2 TO ARG2.

High level analysis

A quick search for some of the keywords used confirms that this is indeed code written in the language of the Elders: Caobaol. This is our first time dealing with Cobol, but this sure looks like a classic crackme.

  1. The program expects a 28 character input
  2. A series of operations is applied to our input (in 002-MAGIC-OP and 003-MAGIC-OP-SUB)
  3. The resulting array is compared to one built in memory by `001-SET-FLAG-KEY

What is not obvious to us though, is how to decode the expected array of values.

Python implementation and solution

With a lot of help from IBM’s COBOL documentation, we decided to reimplement the program in a more modern and familiar language:

from string import printable
from sys import exit

key_len = 28
key_value = [108,102,107,109,7,105,101,104,101,102,27,121,126,98,111,105,107,104,107,102,108,106,124,101,120,99,126,25]
char_index = 0
answer_of_life = 42
bit_val = 0

def magic_op(arg1, arg2):
    global bit_val
    bit_val = 1
    retrn = 0
    if arg1 != 0 or arg2 != 0:
        while True:
            arg1, arg2, retrn = magic_op_sub(arg1, arg2, retrn)
            if arg1 == 0 and arg2 == 0:
                break
    return retrn

def magic_op_sub(arg1, arg2, retrn):
    global bit_val
    quotient1 = arg1//2
    remainder1 = arg1 - quotient1 *2
    quotient2 = arg2//2
    remainder2 = arg2 - quotient2 *2
    if remainder1 != remainder2:
        retrn += bit_val
    bit_val *= 2
    return quotient1,quotient2,retrn


def main(user_key):
#   print("PLEASE ENTER THE KEY ("+str(key_len)+" chars")
    is_valid =1
    char_index = 0
    while char_index < len(user_key):
        arg1 = ord(user_key[char_index])
        arg2 = key_value[char_index]
        val = magic_op(arg1, arg2)
        if val != answer_of_life:
            is_valid = 0
        char_index += 1
    if is_valid:
        return 1
    else:
        return 0

# Bruteforce code starts here
flag = ""
while len(flag) != 28:
    char_valid = 0
    for c in printable:
        char_valid = main(flag + c)
        if char_valid:
            flag = flag + c
            #Having the flag appear one character at a time is very satisfying and lets us know our program is working if it's taking a long time
            print(flag)
            break
    else:
        print("NOOO")
        exit()

Since it was still not obvious how to invert the transformations applied to our input by the program, we decided to bruteforce it. With some minor modifications to the original program’s main function, we can easily have it validate only a portion of the input at a time. This allows us to find one character at a time for a worst case scenario of O = len(string.printable) * 28 (2800) instead of O = len(string.printable) ** 28 (100000000000000000000000000000000000000000000000000000000)

It barely takes any time at all to give us the flag

$ time python cabal.py
[...]
python cabal.py  0.06s user 0.01s system 99% cpu 0.076 total

Back to Home


Hackez la Rue! | © Hubert Hackin'' | 2024-05-27 | theme hugo.386