Created
August 21, 2013 13:10
-
-
Save Edward-H/6294273 to your computer and use it in GitHub Desktop.
COBOL solution to /r/dailyprogrammer's Challenge #132.
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
ID DIVISION. | |
PROGRAM-ID. assembler. | |
INPUT-OUTPUT SECTION. | |
FILE-CONTROL. | |
SELECT asm-file ASSIGN "tiny.asm" | |
ORGANIZATION LINE SEQUENTIAL | |
FILE STATUS file-status | |
. | |
DATA DIVISION. | |
FILE SECTION. | |
FD asm-file. | |
01 asm-statement PIC X(30). | |
WORKING-STORAGE SECTION. | |
01 file-status PIC XX. | |
78 No-Args VALUE SPACES. | |
78 One-Num VALUE "a". | |
78 One-Var VALUE "[a]". | |
78 One-Num-Var VALUE "a [a]". | |
78 One-Num-Two-Vars VALUE "a [a] [a]". | |
78 One-Var-Num VALUE "[a] a". | |
78 Num-Var-Num VALUE "a [a] a". | |
78 Two-Vars VALUE "[a] [a]". | |
78 Two-Vars-One-Num VALUE "[a] [a] a". | |
78 Two-Nums VALUE "a a". | |
78 Three-Vars VALUE "[a] [a] [a]". | |
01 Statement TYPEDEF. | |
03 mnemonic PIC X(6). | |
03 params PIC X(14). | |
78 Num-Instructions VALUE 37. | |
78 Halt-Code VALUE 255. | |
01 instructions-area. | |
03 instructions-values. | |
05 FILLER PIC X(20) VALUE "AND " & Two-Vars. | |
05 FILLER PIC X(20) VALUE "AND " & One-Var-Num. | |
05 FILLER PIC X(20) VALUE "OR " & Two-Vars. | |
05 FILLER PIC X(20) VALUE "OR " & One-Var-Num. | |
05 FILLER PIC X(20) VALUE "XOR " & Two-Vars. | |
05 FILLER PIC X(20) VALUE "XOR " & One-Var-Num. | |
05 FILLER PIC X(20) VALUE "NOT " & One-Var. | |
05 FILLER PIC X(20) VALUE "MOV " & Two-Vars. | |
05 FILLER PIC X(20) VALUE "MOV " & One-Var-Num. | |
05 FILLER PIC X(20) VALUE "RANDOM" & One-Var. | |
05 FILLER PIC X(20) VALUE "ADD " & Two-Vars. | |
05 FILLER PIC X(20) VALUE "ADD " & One-Var-Num. | |
05 FILLER PIC X(20) VALUE "SUB " & Two-Vars. | |
05 FILLER PIC X(20) VALUE "SUB " & One-Var-Num. | |
05 FILLER PIC X(20) VALUE "JMP " & One-Var. | |
05 FILLER PIC X(20) VALUE "JMP " & One-Num. | |
05 FILLER PIC X(20) VALUE "JZ " & Two-Vars. | |
05 FILLER PIC X(20) VALUE "JZ " & One-Var-Num. | |
05 FILLER PIC X(20) VALUE "JZ " & One-Num-Var. | |
05 FILLER PIC X(20) VALUE "JZ " & Two-Nums. | |
05 FILLER PIC X(20) VALUE "JEQ " & Three-Vars. | |
05 FILLER PIC X(20) VALUE "JEQ " & One-Num-Two-Vars. | |
05 FILLER PIC X(20) VALUE "JEQ " & Two-Vars-One-Num. | |
05 FILLER PIC X(20) VALUE "JEQ " & Num-Var-Num. | |
05 FILLER PIC X(20) VALUE "JLS " & Three-Vars. | |
05 FILLER PIC X(20) VALUE "JLS " & One-Num-Two-Vars. | |
05 FILLER PIC X(20) VALUE "JLS " & Two-Vars-One-Num. | |
05 FILLER PIC X(20) VALUE "JLS " & Num-Var-Num. | |
05 FILLER PIC X(20) VALUE "JGT " & Three-Vars. | |
05 FILLER PIC X(20) VALUE "JGT " & One-Num-Two-Vars. | |
05 FILLER PIC X(20) VALUE "JGT " & Two-Vars-One-Num. | |
05 FILLER PIC X(20) VALUE "JGT " & Num-Var-Num. | |
05 FILLER PIC X(20) VALUE "APRINT" & One-Var. | |
05 FILLER PIC X(20) VALUE "APRINT" & One-Num. | |
05 FILLER PIC X(20) VALUE "DPRINT" & One-Var. | |
05 FILLER PIC X(20) VALUE "DPRINT" & One-Num. | |
05 FILLER PIC X(20) VALUE "HALT " & No-Args. | |
03 instructions-table REDEFINES instructions-values. | |
05 instructions USAGE Statement OCCURS Num-Instructions TIMES | |
INDEXED BY ins-idx. | |
01 work-statement PIC X(30). | |
01 instruction USAGE Statement. | |
01 arg PIC X(5). | |
01 hex PIC X(4). | |
01 hex-num PIC 999. | |
01 i PIC 999. | |
PROCEDURE DIVISION. | |
DECLARATIVES. | |
asm-file-error SECTION. | |
USE AFTER STANDARD ERROR PROCEDURE ON asm-file. | |
DISPLAY "An unexpected error occurred while using tiny.asm." | |
DISPLAY "Error code " file-status | |
DISPLAY "The program will terminate." | |
CLOSE asm-file | |
GOBACK | |
. | |
END DECLARATIVES. | |
main-line. | |
OPEN INPUT asm-file | |
*> Read through the file, displaying op-codes for the assembly. | |
PERFORM UNTIL 1 <> 1 | |
READ asm-file | |
AT END | |
EXIT PERFORM | |
END-READ | |
MOVE asm-statement TO work-statement | |
*> Split mnemonic from work-statement, leaving the arguments. | |
CALL "get-and-remove-next-token" USING work-statement, | |
mnemonic OF instruction | |
MOVE FUNCTION UPPER-CASE(mnemonic OF instruction) | |
TO mnemonic OF instruction | |
*> Create a generic form of the arguments, i.e. replace numbers | |
*> with 'a'. | |
PERFORM UNTIL work-statement = SPACES | |
CALL "get-and-remove-next-token" USING work-statement, arg | |
IF arg (1:1) = "[" | |
MOVE One-Var TO arg | |
ELSE | |
MOVE One-Num TO arg | |
END-IF | |
STRING params OF instruction DELIMITED BY " ", " ", arg | |
INTO params OF instruction | |
END-PERFORM | |
*> Remove leading space | |
MOVE params OF instruction (2:) TO params OF instruction | |
*> Search through instructions for matching mnemonic and args. | |
SET ins-idx, i TO 1 | |
SEARCH instructions VARYING i | |
AT END | |
DISPLAY asm-statement " could not be matched. Skipping..." | |
WHEN instructions (i) = instruction | |
PERFORM display-op-codes | |
END-SEARCH | |
END-PERFORM | |
CLOSE asm-file | |
GOBACK | |
. | |
display-op-codes. | |
IF mnemonic OF instruction = "HALT" | |
MOVE Halt-Code TO hex-num | |
PERFORM display-hex-num | |
ELSE | |
*> Display instruction index in hex, which equals the | |
*> instruction's op-code. | |
SUBTRACT 1 FROM i GIVING hex-num | |
PERFORM display-hex-num | |
MOVE asm-statement TO work-statement | |
CALL "get-and-remove-next-token" USING work-statement, arg | |
*> Display arguments in hex. | |
PERFORM UNTIL work-statement = SPACES | |
CALL "get-and-remove-next-token" USING work-statement, arg | |
MOVE FUNCTION numval(arg) TO hex-num | |
PERFORM display-hex-num | |
END-PERFORM | |
END-IF | |
DISPLAY SPACE | |
. | |
display-hex-num. | |
CALL "to-hex" USING CONTENT hex-num, REFERENCE hex | |
DISPLAY hex " " NO ADVANCING | |
. | |
END PROGRAM assembler. |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
*> Puts the first space-delimited word/number from input-str into | |
*> token, and left-shifts input-str over it. | |
*> This was salvaged from my solution of Challenge #136. | |
ID DIVISION. | |
PROGRAM-ID. get-and-remove-next-token. | |
DATA DIVISION. | |
LOCAL-STORAGE SECTION. | |
01 offset PIC 99 VALUE 0. | |
LINKAGE SECTION. | |
01 str PIC X(30). | |
01 token PIC X(30). | |
PROCEDURE DIVISION USING REFERENCE str, token. | |
INSPECT str TALLYING offset FOR CHARACTERS BEFORE SPACE | |
MOVE str (1:offset) TO token | |
ADD 2 TO offset | |
MOVE str (offset:) TO str | |
GOBACK | |
. | |
END PROGRAM get-and-remove-next-token. |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
IDENTIFICATION DIVISION. | |
PROGRAM-ID. to-hex. | |
DATA DIVISION. | |
LOCAL-STORAGE SECTION. | |
01 i PIC 9. | |
01 rem PIC 99. | |
LINKAGE SECTION. | |
01 num PIC 999. | |
01 hex-out PIC X(4). | |
PROCEDURE DIVISION USING num, hex-out. | |
IF 255 < num | |
DISPLAY "Numbers larger than 255 are not supported." | |
MOVE SPACES TO hex-out | |
GOBACK | |
END-IF | |
MOVE "0x00" TO hex-out | |
*> Algorithm adapted from Wikipedia: | |
*> http://en.wikipedia.org/wiki/Hexadecimal#Division-remainder_in_source_base | |
PERFORM VARYING i FROM 1 BY 1 UNTIL num = 0 | |
DIVIDE num BY 16 GIVING num REMAINDER rem | |
IF rem < 10 | |
MOVE rem (2:1) TO hex-out (5 - i:1) | |
ELSE | |
MOVE FUNCTION CHAR((rem - 10) + FUNCTION ord("A")) | |
TO hex-out (5 - i:1) | |
END-IF | |
END-PERFORM | |
GOBACK | |
. | |
END PROGRAM to-hex. |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment