; Routines to convert Data General Eclipse(IBM 360) binary to ; Vax binary. ; Write output to registers and let VAX MOV instructions ; move the data from the register to memory (rearranging the bytes ; as VAX requires). .TITLE DG_VAX .PSECT ITWO ; Convert Integer*2(16 bits) ; Integer*2 function. To call: INTEGER*2 ITWO,IVAX,IDG ; IVAX=ITWO(IDG) .ENTRY ITWO ^M<> EXTZV #8,#8,@4(AP),R0 ;put least sig. input byte into bits 7:0 of R0 ;and zero rest of R0 INSV @4(AP),#8,#8,R0 ;put most sig. input byte into bits 15:8 of R0 RET .PSECT IFOUR ; Convert Integer*4(32 bits, 'double precision integer') ; Integer*4 function. To call: INTEGER*4 IFOUR,IVAX,IDG ; IVAX=IFOUR(IDG) .ENTRY IFOUR ^M<> EXTZV #24,#8,@4(AP),R0 ;put least sig. input byte into bits 7:0 of R0 ;and zero rest of R0 INSV @4(AP),#24,#8,R0 ;put most sig.input byte into ;bits 31:24 of R0 MOVL 4(AP),R1 ;addr of input into R1 INSV 1(R1),#16,#8,R0 ;put 2nd most sig. input byte into ;bits 23:16 of R0 INSV 2(R1),#8,#8,R0 ;put 3rd most sig. input byte into ;bits 15:8 of R0 RET .PSECT REAL EIGHT: .BYTE 0 .ENTRY REIGHT ^M ; Convert Real*8(64 bits), double precision real ; To call: REAL*8 RDG,RVAX ; INTEGER*4 IER ; ; CALL REIGHT(RDG,RVAX,IER) ; ; RDG - REAL*8 D.G input ; RVAX - REAL*8 VAX output ; IER - integer error flag ; 0 = okay ; 1 = underflow, RVAX is set to 0. ; 2 = overflow, RVAX is set to largest ; number possible ; (VAX exponent is ~+38 to -38, ; IBM is ~+75 to -75) ; 3 = illegal input format, RVAX is unchanged MOVB #1,EIGHT ;is real*8 JMP REAL0 .ENTRY RFOUR ^M ; Convert Real*4(32 bits), single precision real ; To call: REAL*4 RDG,RVAX ; INTEGER*4 IER ; ; CALL RFOUR(RDG,RVAX,IER) ; ; RDG - REAL*4 D.G input ; RVAX - REAL*4 VAX output ; IER - integer error flag ; 0 = okay ; 1 = underflow, RVAX is set to 0. ; 2 = overflow, RVAX is set to largest ; number possible ; (VAX exponent is ~+38 to -38, ; IBM is ~+75 to -75) ; 3 = illegal input format, RVAX is unchanged MOVB #0,EIGHT ;not real*8 ; Init REAL0: MOVL #0,@12(AP) ;zero error flag(3rd argument) MOVL #0,R0 ;set mantissa work registers to zero. MOVL #0,R1 MOVL #0,R2 ;set exponent work register to zero. MOVL 4(AP),R3 ;store address of input value in R3 ; Input value is zero? CMPW (R3),#0 ;sign bit, 7 exp. bits, 8 most sig. mantissa ;bits all zero? BNEQ REAL1A CMPB EIGHT,#1 ;yes, return zero and no error(assume rest of ;mantissa is zero). BEQL REAL1B MOVF R0,@8(AP) ;real*4 entry. store in RVAX from R0. RET REAL1B: MOVD R0,@8(AP) ;real*8 entry. store in RVAX from R0,R1. RET ; No, check that 4 most sig. bits of mantissa are not equal to zero. REAL1A: BITB #^XF0,1(R3) BNEQ REAL1 ;okay, non-zero ; illegal format MOVL #3,@12(AP) ;set error flag = 3 RET ;leave result alone and return ; Convert exponent ( Vax exp is 1 >= (D.G. exp * 4) - 128 <= 255 ) REAL1: EXTZV #0,#7,(R3),R2 ;put 7 bit D.G. exp in R2 and zero rest of R2 ASHL #2,R2,R2 ;multiply by 4 SUBL2 #128,R2 ;subtract 128 ; Convert mantissa MOVB 1(R3),R0 ;most sig. byte to R0 ASHL #8,R0,R0 ;shift the byte left 8 bits MOVB 2(R3),R0 ;2nd most sig. byte to R0 ASHL #8,R0,R0 ;shift the byte left 8 bits MOVB 3(R3),R0 ;3rd most sig. byte to R0 CMPB EIGHT,#1 ;real*8 entry ? BNEQ REAL2 ;if not, branch MOVB 4(R3),R1 ;4th most sig. byte to R1 ASHL #8,R1,R1 ;shift the byte left 8 bits MOVB 5(R3),R1 ;5th most sig. byte to R1 ASHL #8,R1,R1 ;shift the byte left 8 bits MOVB 6(R3),R1 ;6th most sig. byte to R1 ASHL #8,R1,R1 ;shift the byte left 8 bits MOVB 7(R3),R1 ;least most sig. byte to R1 REAL2: BBS #23,R0,REAL3 ;mantissa normalized? ASHL #1,R0,R0 ;shift R0 left by one BBC #31,R1,REAL2A ;branch if sign bit in R1 is off. BISL2 #1,R0 ;shift into R0 bit 31 of R1 REAL2A: ASHL #1,R1,R1 ;shift R1 left by one DECL R2 ;subtract 1 from the binary exponent JMP REAL2 ; mantissa is normalized. Is exp in range? REAL3: CMPL R2,#1 ;>= 1 ? BGEQ REAL4 MOVL #1,@12(AP) ;no, underflow. set IER=1, return RVAX=0. MOVL #0,R0 MOVL #0,R1 JMP REAL8 REAL4: CMPL R2,#255 ;<= 255 ? BLEQ REAL5 MOVL #2,@12(AP) ;no, overflow. set IER=2, return RVAX large. MCOML #0,R0 ;turn all bits on in R0 and in R1 MOVL R0,R1 JMP REAL6 ; exponent in range, move it to R0 over the most sig. bit of mantissa. REAL5: INSV R2,#23,#8,R0 ;store 8 bit exp in R0 ; Move sign bit to R0. REAL6: BBC #7,(R3),REAL7 ;branch if sign bit is zero BISL2 #^X80000000,R0 ;set sign bit to 1 in R0 JMP REAL8 REAL7: BICL2 #^X80000000,R0 ;set sign bit to 0 in R0 ; store result in 2nd argument REAL8: ROTL #16,R0,R0 ;rotate into Vax register real format. CMPB EIGHT,#1 BEQL REAL9 MOVF R0,@8(AP) ;real*4 entry. store in RVAX from R0. RET REAL9: ROTL #16,R1,R1 ;rotate into Vax register real format MOVD R0,@8(AP) ;real*8 entry. store in RVAX from R0,R1. RET .END