The MASM Forum

General => The Campus => Topic started by: hfheatherfox07 on December 21, 2012, 03:44:57 PM

Title: binary to ascii
Post by: hfheatherfox07 on December 21, 2012, 03:44:57 PM
Hi,
I wanted to do a binary to ASCII conversion and I found this snippet
what kind of asm is this ???

Thank you!
Title: Re: binary to ascii
Post by: anta40 on December 21, 2012, 04:54:58 PM
Looks like PIC (http://www.microchip.com/) assembly.
Title: Re: binary to ascii
Post by: hfheatherfox07 on December 21, 2012, 04:58:38 PM
Thanks
I got an ASCII to Binary but not Binary To ASCII
I guess I better see if I can convert it to MASM some how lol
Title: Re: binary to ascii
Post by: jj2007 on December 21, 2012, 05:35:31 PM
If it's for fun, sit down and reflect, then roll your own.
If it's for getting a job done, look into \masm32\help\masmlib.chm ;)
Title: Re: binary to ascii
Post by: Farabi on December 21, 2012, 06:12:09 PM
Have a look at MASMLib

bin2hex proc lpString:DWORD,lnString:DWORD,lpbuffer:DWORD


Title: Re: binary to ascii
Post by: hfheatherfox07 on December 21, 2012, 07:39:33 PM
Quote from: Farabi on December 21, 2012, 06:12:09 PM
Have a look at MASMLib

bin2hex proc lpString:DWORD,lnString:DWORD,lpbuffer:DWORD

I was Going to do bintohex than hextoascii but I get an error with bin2hex:

include \masm32\include\masm32rt.inc

.data
bindata  db "01001000 01100101 01101100 01101100 01101111"
hstr     db 60 dup(0)
HEX_PRE  db "%X", 32, 0 ; prefix hex, 32 for space, 0 to end
mybuffer db 4096 dup(?) ; total converted string
szCapt   db "Binary Hello in Hex", 0
.code

start:

invoke bin2hex,ADDR bindata,SIZEOF bindata,ADDR hstr
invoke lstrcat, ADDR mybuffer, ADDR hstr
invoke MessageBox,NULL,addr mybuffer,addr szCapt,MB_OK
; The result should be 48 65 6C 6C 6F
Invoke ExitProcess,0

end start


ASCII hello = Binary  01001000 01100101 01101100 01101100 01101111
Should give 48 65 6C 6C 6F in Hex
Title: Re: binary to ascii
Post by: Farabi on December 21, 2012, 07:59:26 PM
What do you mean by binary? An ASCII Binary or a raw binary format?
Title: Re: binary to ascii
Post by: hfheatherfox07 on December 21, 2012, 08:01:03 PM
I will Be inputting this into the edit box  01001000 01100101 01101100 01101100 01101111
So ASCII Binary
Title: Re: binary to ascii
Post by: jj2007 on December 21, 2012, 08:06:26 PM
You need two conversions, the first being bin2byte_ex. However, I couldn't get it to work - Hutch will show you an example when it's daytime down under.

If it's urgent - this one works: 48 65 6C 6C 6F

include \masm32\MasmBasic\MasmBasic.inc        ; download (http://masm32.com/board/index.php?topic=94.0)
.data
bindata        db "01001000 01100101 01101100 01101100 01101111"
        Init
        mov esi, offset bindata
@@:
        void Val(Cat$(Left$(esi, 8 )+"b"))
        cmp edx, -127        ; -127=flag conversion failed
        je @F
        add esi, 9
        Print Hex$(al), " "    ; or invoke lstrcat, offset buffer, Hex$(al)
        jmp @B
@@:
        Inkey "ok?"
        Exit
end start
Title: Re: binary to ascii
Post by: hfheatherfox07 on December 21, 2012, 08:14:12 PM
I found this TASM Bin2ASCII proc
But It is crashing ....
.386
.model flat,stdcall
option casemap:none

include  \masm32\include\windows.inc
include  \masm32\include\kernel32.inc
include  \masm32\include\user32.inc

includelib  \masm32\lib\kernel32.lib
includelib  \masm32\lib\user32.lib


Bin2ASCII proto
.data

bindata  db "01001000 01100101 01101100 01101100 01101111"
hstr     db 60 dup(0)
HEX_PRE  db "%X", 32, 0 ; prefix hex, 32 for space, 0 to end
mybuffer db 4096 dup(?) ; total converted string
szCapt   db "Binry To ASCII", 0

.data

.code

start:
push offset bindata
call Bin2ASCII

;invoke lstrcat, ADDR mybuffer, ADDR hstr
invoke MessageBox,NULL,addr mybuffer,addr szCapt,MB_OK

Invoke ExitProcess,0
Bin2ASCII   proc   
    mov     bx, 10 ; base ss. 10 for decimal, etc.
oi2:
    xor     dx,dx
    div     bx
; Divide the number by the base ss. In the remainder of the latter figure is obtained.
; mmediately display it impossible, so keep it in the stack.
    push    dx
    inc     cx
; And A with the private repeat the same thing, separated from it by another
; figure on the right, as there will be zero, which means that more
; left only zeros.
    test    ax, ax
    jnz     oi2
; ?Now, on to a conclusion.
    mov     ah, 02h
oi3:
    pop     dx
; Retrieve the next number, translate it into a symbol and display.
    add     dl, '0'
    int     21h
; Repeat as many times as numbers counted.
    loop    oi3
    ret
Bin2ASCII   endp
end start


Original Tasm  http://www.cyberforum.ru/assembler/thread720808-page2.html

;DOS, TASM, COM-????
;tasm.exe /m
;tlink.exe /t /x
;
.model tiny
.code
.386
org 100h
start:
    mov ah,10   ;???? ??????
    lea dx,str
    mov di,dx
    int 21h

    mov ah,2    ;??????? ??????
    mov dl,10
    int 21h

    inc di      ;?? ????? ????????? ????????

    xor ax,ax   ;??????? ????????? AH-??????? ????? ?????
    xor bx,bx

    mov bl,[di] ;????? ????????? ????????
    inc di      ;?? ????????? ??????
    mov [di+bx],byte ptr ' ' ;? ????? ?????? ???????? ??????
             ;??? ???? ???-?? ??? ????? ???? ? ?????????
    inc [len]   ;????????? ????? ?????? ? ?????? ?????? ???????

m1:
    mov cl,[len]    ;
    test cl,cl  ;???? 0, ?????
    jz okString

;????? ???????
    call Probel

;?????????? ????? ???????? ? AH ? ????? ?????? ????? ????? ? BP
    cmp cl,ah
    jle m1
    mov ah,cl
    mov bp,dx
    jmp short m1    ;?? ????????? ?????

okString:
    test ah,ah  ;?? 0 - ???? ?????
    jnz okWord

    ret     ;????? ?? ?????????

okWord:
    call Schet

;????? ?? ?????
    call Bin2ASCII

    xor ax,ax   ;????? ??????? ???????
    int 16h

    ret     ;????? ?? ?????????
;----------?????????----------------
Bin2ASCII   proc    near
    mov     bx, 10 ; ????????? ??. 10 ??? ???????????? ? ?.?.
oi2:
    xor     dx,dx
    div     bx
; ????? ????? ?? ????????? ??. ? ??????? ?????????? ????????? ?????.
; ????? ???????? ?? ??????, ??????? ???????? ?? ? ?????.
    push    dx
    inc     cx
; ? ? ??????? ????????? ?? ?? ?????, ??????? ?? ???? ?????????
; ????? ??????, ???? ?? ????????? ????, ??? ??????, ??? ??????
; ????? ?????? ????.
    test    ax, ax
    jnz     oi2
; ?????? ????????? ? ??????.
    mov     ah, 02h
oi3:
    pop     dx
; ????????? ????????? ?????, ????????? ?? ? ?????? ? ???????.
    add     dl, '0'
    int     21h
; ???????? ????? ??????? ???, ??????? ???? ?????????.
    loop    oi3
    ret
Bin2ASCII   endp
;------------------------
Schet   proc    near
    mov cl,ah
    xor ax,ax
    mov di,bp
m3:
    cmp [di],byte ptr 'c'
    jnz m4
    inc al
m4:
    inc di
    loop m3
    ret
Schet   endp
;------------------------
Probel  proc    near
    mov dx,di   ;??? ?????????? ????? ????? DX-?????? ?????
    mov al,' '
    repne scasb ;

    mov cx,di   ;DI-????? ?????
    sub cx,dx   ;DX-?????? ?????. DI-DX=CX=????? ?????
    sub [len],cl    ;????? ????? ??????
    ret
Probel  endp
;--------??????-----------
str db 100
len db ?

    end start


Title: Re: binary to ascii
Post by: dedndave on December 21, 2012, 08:20:05 PM
that's not binary, it's an "ASCII binary string (with spaces)"   :P
i doubt there is a routine for that in the masm32 library because it's kind of a "special" case

the example you show has 5 bytes of data
if you limit it to 8 bytes, it would be pretty simple, because it would fit into an unsigned dword
to strip out spaces, you might just skip over anything that isn't an ASCII "0" or an ASCII "1"
they could be commas, periods, spaces, hyphens, etc
and, of course, terminate at a null byte
it would be a little harder if you wanted to verify the "8 bits then space" format

speed probably isn't critical, because you aren't going to convert 100,000 of these strings - just 1
Title: Re: binary to ascii
Post by: dedndave on December 21, 2012, 08:24:46 PM
the expected format is "01001000 01100101 01101100 01101100 01101111"
how do you want the routine to respond if they enter "1001000 1100101 1101100 1101100 1101111" ?
or "1 1 1 1 1     1 1" ?
or "101010101010101010101010" ?

how is this thing going to be used ?
you need to define a set of rules   :P
Title: Re: binary to ascii
Post by: jj2007 on December 21, 2012, 08:45:20 PM
Quote from: dedndave on December 21, 2012, 08:24:46 PM
how do you want the routine to respond if they enter "1001000 1100101 1101100 1101100 1101111" ?
or "1 1 1 1 1     1 1" ?
or "101010101010101010101010" ?

That can be tricky indeed.

include \masm32\MasmBasic\MasmBasic.inc        ; download (http://masm32.com/board/index.php?topic=94.0)
.data
bindata        db "1000 101 1101100 01101100 11   111 0  11 10000 10101010 11 11 000000000"

        Init
        mov esi, offset bindata        ; or mov esi, Win$(hEdit)
@@:
        void Val(Cat$(Left$(esi, Instr_(esi, " ")-1)+"b"))
        cmp edx, -127        ; -127=flag conversion failed
        je @F
        movzx edx, dl        ; get bytes used
        add esi, edx          ; advance source pointer
        Print Hex$(al), " "        ; or invoke lstrcat, offset buffer, Hex$(al)
        .Repeat
                lodsb
        .Until al>="0" || !al
        dec esi
        test al, al
        jne @B
@@:
        Inkey "ok?"
        Exit
end start

Output:
08 05 6C 6C 03 07 00 03 10 AA 03 03 00
Title: Re: binary to ascii
Post by: hfheatherfox07 on December 21, 2012, 08:49:47 PM
Quote from: dedndave on December 21, 2012, 08:24:46 PM
how is this thing going to be used ?
you need to define a set of rules   :P


Ya you opened my eyes dedndave .....
I got a routine that converts ASCII strings into Binary ASCII
as I posted .....
I guess all this came from seeing posts with people's signatures in ASCII binary , I guess to be cool and be like Neo from matrix , just wanted to make a little converter to allow me to read what they wrote....
So the user will paste the ASCII as I posted it ...
But it is a good question , what will happen if They get that ASCII binary off the net
And it is spaced differently .....
Title: Re: binary to ascii
Post by: dedndave on December 21, 2012, 08:54:32 PM
i think i would be inclined to pre-parse the string, then do a conversion loop
one case that needs clarification is if there is a portion of the string that has more than 8 bin digits

but, you might parse through the string....
first, push a 0 onto the stack
find the address of the beginning of each series of "1"s and "0"s and push it on the stack
let the conversion routine identify the end of each series
pop the addresses off the stack and call the routine
when you pop a 0, you are done
reverse the bytes and convert it to a big binary value   :biggrin:

oh, ok - you want to convert them to ASCII bytes - that's a little different
Title: Re: binary to ascii
Post by: dedndave on December 21, 2012, 09:00:05 PM
really, if they have "10 0101", we can just zero-extend those and call it the same as "00000010 00000101"
the tricky one is how to handle "10101010010101010101010" - string sections longer than 8 bits

here is another one that might throw a wrench in the works...
"01010 11010000 11010200"   :biggrin:
Title: Re: binary to ascii
Post by: hfheatherfox07 on December 21, 2012, 09:02:42 PM
 :eusa_snooty:I am beginning to suspect that it should not have any space
I google "binary to ASCII text converters online
And it seems that they do not have spaces

http://m.branah.com/ascii-converter

Even if you enter 2 words with a space inbetween them
The binary ASCII is a long string
So .... I'm going to have to relook that routine that I have

Anyway it is 5 AM here
Going to hit the hey , I will think clearly after a nap
Thank you all for all the help :)
Title: Re: binary to ascii
Post by: jj2007 on December 21, 2012, 09:13:13 PM
Quote from: dedndave on December 21, 2012, 09:00:05 PM
here is another one that might throw a wrench in the works...
"01010 11010000 11010200"   :biggrin:

I'm afraid even my routine in Reply #12 doesn't throw an error... :redface:
Title: Re: binary to ascii
Post by: hfheatherfox07 on December 21, 2012, 09:14:49 PM
Here is the tool that I got to convert ASCII to Binary

Title: Re: binary to ascii
Post by: FORTRANS on December 22, 2012, 01:22:48 AM
Hi,

   I made a fixed point binary, hex, and decimal converter
back when.  It's in the Archive2 subforum as  5486_FIX2DEC.zip.
A DOS program, but it may give you some ideas.  It is an
older version so if anyone wants an updated version I can
dig it out and post it.

Regards,

Steve N.
Title: Re: binary to ascii
Post by: hfheatherfox07 on December 22, 2012, 06:01:21 AM
what I am trying to accomplish is something like this http://www.roubaixinteractive.com/PlayGround/Binary_Conversion/Binary_To_Text.asp

I need to take out the space in the ascii2bin routine in ASCII2BIN.zip and I can't get it to work

I did find another ascii2bin but It gives me wrong bin?

.486p
.model flat,stdcall
option casemap:none

include \masm32\include\windows.inc
include \masm32\include\masm32.inc
include \masm32\include\kernel32.inc
include \masm32\include\user32.inc

includelib \masm32\lib\masm32.lib
includelib \masm32\lib\kernel32.lib
includelib \masm32\lib\user32.lib

hex2abin proto :DWORD,:DWORD

.data
szHexString  db "48 65 6C 6C 6F" ; Hello
hstr     db 60 dup(0)
mybuffer db 4096 dup(?) ; total converted string
szCapt   db "Hex To Binary", 0
.code

start:

invoke hex2abin,addr szHexString,addr hstr
invoke lstrcat, addr mybuffer,addr hstr
invoke MessageBox,NULL,addr mybuffer,addr szCapt,MB_OK
Invoke ExitProcess,0
hex2abin proc uses edi hexnumber:DWORD, lpbuf:DWORD

mov edx,hexnumber
mov ecx,32
mov edi,lpbuf
@@:
shl edx,1 ;transfers the bits to the C flag one by one
mov al,18h ;30h (ASCII 0)/2
rcl al,1 ;gets the ASCII 0 back + the C flag as 0 or 1
stosb
dec ecx
jnz @B
mov al,0
stosb
ret

hex2abin endp
end start
Title: Re: binary to ascii
Post by: hfheatherfox07 on December 22, 2012, 06:04:01 AM
Here is a Bin2Ascii.ASM that I found , but I can not get it to work

; Here is a version of Bin2Ascii that allows the quotient to overflow, but
; takes care that the resulting answer will be correct.  It is certainly
; shorter than the version in the sample solution.

; Note, however, that if Virgo followed the Encoding Reference Manual strictly,
; this version would not work.

; For DIV, the Encoding Reference Manual states:

; "If the quotient is too large to fit in the low half of the dividend, then the
; quotient and remainder are undefined and a Type 0 software interrupt is performed."

; Here, we take advantage of the fact that with Virgo, the results of a 32 bit DIV
; of this form are that the remainder is correct and the quotient is the low
; word of the quotient.

; Note that this subroutine will not assemble on its own.  (Replace the Bin2Ascii
; in the sample solution with this file and then assemble and execute.)

;*****************************************************************************
;*
;* NAME:    Bin2Ascii
;*
;* void Bin2Ascii( unsigned long int & BinVal, char & AsciiText[] )
;*
;* Purpose: converts 32-bit binary value BinVal to $-terminated AsciiText string
;* (AsciiText[] must be large enough to hold the Ascii representation of
;* the largest unsigned long integer value + the terminator)
;* Note: supresses leading zeros (and blanks) during conversion
;*
;* Accepts: address of double word (little endian), and address of character string
;* Returns: nothing
;*****************************************************************************

Bin2Ascii:
push bp
mov bp,sp
push ax
push bx
push cx
push dx
push si
push di

mov bx,word ptr[bp+4] ; address of long int
mov ax, [bx] ; low word of long int
add bx,2
mov dx, [bx] ; high word of long int
mov bx,word ptr[bp+6] ; address of string

; set string to 10 blanks plus a $ sign (cannot assume that it is set up right)
mov si,0
BlankLoop:
mov byte ptr[bx+si],' '
inc si
cmp si,10
jne BlankLoop
mov byte ptr[bx+si],'$'

mov si,9 ; start with 10th digit (offset)
DigitLoop:
mov cx,dx ; store a copy of dx in cx

div word ptr[constant10] ; divide dx:ax by 10 (quotient in ax, remainder in dx)
add dx,30h ; add 30h to remainder to convert to ascii

mov byte ptr[bx+si],dl ; store ascii character at offset si
dec si ; decrement offset

mov di,ax ; store a copy of quotient in di
mov ax,cx ; move old dx into ax
mov dx,0 ; set dx to 0
div word ptr[constant10] ; divide old dx by 10 (quotient in ax, remainder in dx)

mov dx,ax ; move quotient into dx
mov ax,di ; move old quotient into ax (thus dx:ax contains quotient of dx:ax / 10)

cmp ax,0 ; if both ax and dx are 0 we are done, otherwise loop again
jne DigitLoop

cmp dx,0
jne DigitLoop

; now we need to fix up the string as it is currently right justified and should be left justified
cmp si,-1
je  DoneBin2Ascii ; if si is -1 the string is full and thus left justified so we are done
add si,1
mov di,0
JustifyLoop:
mov cl,byte ptr[bx+si]
mov byte ptr[bx+di],cl
inc si
inc di
cmp si,10
jbe JustifyLoop

DoneBin2Ascii:
pop di
pop si
pop dx
pop cx
pop bx
pop ax
pop bp
ret


Title: Re: binary to ascii
Post by: hfheatherfox07 on December 22, 2012, 06:32:26 AM
I found another Bin2Hex proc here http://www.purebasic.fr/english/viewtopic.php?p=153495

Why is it crashing?

.486p
.model flat,stdcall
option casemap:none

include \masm32\include\windows.inc
include \masm32\include\masm32.inc
include \masm32\include\kernel32.inc
include \masm32\include\user32.inc

includelib \masm32\lib\masm32.lib
includelib \masm32\lib\kernel32.lib
includelib \masm32\lib\user32.lib

Bin2ASCII proto :DWORD,:DWORD

.data
HEX_PRE           db "%X", 32, 0 ; prefix hex, 32 for space, 0 to end
szBinaryString  db "0100100001100101011011000110110001101111" ; Hello
hBinarystr     db 60 dup(0)
mybuffer db 4096 dup(?) ; total converted string
buffer          db 32 dup(?) ; buffer
szCapt   db "Binary To Hex", 0
.code

start:

invoke Bin2ASCII,addr szBinaryString,addr buffer
invoke wsprintf, ADDR buffer, ADDR HEX_PRE, eax ; buffer = 5dup(0)
invoke lstrcat, ADDR mybuffer, ADDR buffer ; mybuffer db 512 dup(0)
invoke MessageBox,NULL,addr mybuffer,addr szCapt,MB_OK
Invoke ExitProcess,0
Bin2ASCII proc  src:DWORD, dst :DWORD


;the setup
pushad                 ;save all cpu registers

mov esi,src            ;point to source
mov edi,dst            ;point to destination

;mov ecx,size        ;counter into source file  PureBasic
invoke lstrlen, addr szBinaryString
mov ecx, eax ; move src length to ecx

lea ebx,hex_table      ;get the address of the lookup table

or ecx,ecx             ;test it's not 0
jz short done

;now do the work
ALIGN 16      ;make sure the next instruction starts on a 16 byte boundary.
lp:

movzx eax,byte ptr [esi]   ;get next byte
mov edx,[4*eax+ebx]        ;look up HEX

mov [edi],dx               ;write the output
add edi,3                  ;update destination pointer
     
inc esi                    ;update pointer
dec ecx                    ;update count

jns short lp               ;go back for next character on this line

done:

popad                      ;restore all cpu registers

ALIGN 16  ;make sure the lookup table is aligned in memory
hex_table:
dd "  00","  10","  20","  30","  40","  50","  60","  70"
dd "  80","  90","  A0","  B0","  C0","  D0","  E0","  F0"
dd "  01","  11","  21","  31","  41","  51","  61","  71"
dd "  81","  91","  A1","  B1","  C1","  D1","  E1","  F1"
dd "  02","  12","  22","  32","  42","  52","  62","  72"
dd "  82","  92","  A2","  B2","  C2","  D2","  E2","  F2"
dd "  03","  13","  23","  33","  43","  53","  63","  73"
dd "  83","  93","  A3","  B3","  C3","  D3","  E3","  F3"
dd "  04","  14","  24","  34","  44","  54","  64","  74"
dd "  84","  94","  A4","  B4","  C4","  D4","  E4","  F4"
dd "  05","  15","  25","  35","  45","  55","  65","  75"
dd "  85","  95","  A5","  B5","  C5","  D5","  E5","  F5"
dd "  06","  16","  26","  36","  46","  56","  66","  76"
dd "  86","  96","  A6","  B6","  C6","  D6","  E6","  F6"
dd "  07","  17","  27","  37","  47","  57","  67","  77"
dd "  87","  97","  A7","  B7","  C7","  D7","  E7","  F7"
dd "  08","  18","  28","  38","  48","  58","  68","  78"
dd "  88","  98","  A8","  B8","  C8","  D8","  E8","  F8"
dd "  09","  19","  29","  39","  49","  59","  69","  79"
dd "  89","  99","  A9","  B9","  C9","  D9","  E9","  F9"
dd "  0A","  1A","  2A","  3A","  4A","  5A","  6A","  7A"
dd "  8A","  9A","  AA","  BA","  CA","  DA","  EA","  FA"
dd "  0B","  1B","  2B","  3B","  4B","  5B","  6B","  7B"
dd "  8B","  9B","  AB","  BB","  CB","  DB","  EB","  FB"
dd "  0C","  1C","  2C","  3C","  4C","  5C","  6C","  7C"
dd "  8C","  9C","  AC","  BC","  CC","  DC","  EC","  FC"
dd "  0D","  1D","  2D","  3D","  4D","  5D","  6D","  7D"
dd "  8D","  9D","  AD","  BD","  CD","  DD","  ED","  FD"
dd "  0E","  1E","  2E","  3E","  4E","  5E","  6E","  7E"
dd "  8E","  9E","  AE","  BE","  CE","  DE","  EE","  FE"
dd "  0F","  1F","  2F","  3F","  4F","  5F","  6F","  7F"
dd "  8F","  9F","  AF","  BF","  CF","  DF","  EF","  FF"

Bin2ASCII endp
end start
Title: Re: binary to ascii
Post by: jj2007 on December 22, 2012, 06:51:41 AM
Quote from: hfheatherfox07 on December 22, 2012, 06:32:26 AM
I found another Bin2Hex proc here http://www.purebasic.fr/english/viewtopic.php?p=153495

Why is it crashing?

Because a ret is missing in line 67. Still, I haven't understood: Are you testing all these crappy snippets out of interest for others' coding attempts, or do you need a solution? The one in reply #12 works perfectly :biggrin:
Title: Re: binary to ascii
Post by: dedndave on December 22, 2012, 06:56:27 AM
none of them do what you seem to want to do
one is for ascii hex to binary
one is for binary to ascii hex
one is for binary to ascii decimal, which is 16-bit code

the function you want to perform is a very simple one
however, you have to start by defining some rules

what if i give you a string of 1's and 0's, the length of which is not evenly divisible by 8 ?
how do you want your routine to handle that case ?

if it is less than 8 - we can zero-extend it
but, what if there are (21) 1's and 0's ?
Title: Re: binary to ascii
Post by: dedndave on December 22, 2012, 07:05:46 AM
the basic idea of the conversion is something like this....

ASCII "0" is 30h, or 48 decimal, in binary
ASCII "1" is 31h, or 49 decimal, in binary

of course, you may want to check for a null terminator byte, first
if you xor an input byte with 30h....
if it is ASCII "0", the result will be binary 0
if it is ASCII "1", the result will be binary 1
if it is any other value, the result will be > binary 1

you can successively shift those bits into a byte (left-most text digits are higher order bits)
when you have 8 of them, you have your ASCII character

there are a number of tricks you can play to make it fast
but, i wouldn't worry about that - just get a routine that works up and running
Title: Re: binary to ascii
Post by: hfheatherfox07 on December 22, 2012, 07:08:24 AM
ALL I wanted to do is this http://www.roubaixinteractive.com/PlayGround/Binary_Conversion/Binary_To_Text.asp

I will look into this some more......
Title: Re: binary to ascii
Post by: dedndave on December 22, 2012, 07:11:55 AM
i saw that
ok
but, he has a nice pile of 1's and 0's whose length is evenly divisible by 8   :P

here's how he handles it - lol
QuoteError: Malformed binary. Your binary code is must be divisible by 8.
not very clear - he means the length must be divisible by 8

here's how he handles non-printable characters
29º¹2:7294·5
<·º¹'»0¶:4·2—
Title: Re: binary to ascii
Post by: hfheatherfox07 on December 22, 2012, 07:23:54 AM
Well I am working with the assumption that I do for now lo

How to translate this little Part

mov esi,src            ;point to source
mov edi,dst            ;point to destination

;mov ecx,size        ;counter into source file  PureBasic


the  mov ecx,size

I found another one with same deal ....
.data
szHexLookup db "0123456789ABCDEF"

.code

bin2hex:
mov esi, [sourcedata]
mov edi, [targetstring]
mov ecx, [sourcelength]

.process:
lodsb
mov ah, al
and al, 0xF
movzx edx, al
mov al, [szHexLookup + edx]
stosb

shr ah, 4
movzx edx, ah
mov al, [szHexLookup + edx]
stosb

dec ecx
jnz .process


how do you write  mov      ecx, [sourcelength] ?

I get the same wrong results whether I use
mov ecx,sizeof sourcedata   
or     
invoke lstrlen, addr sourcedata
mov ecx, eax ; move src length to ecx


.486p
.model flat,stdcall
option casemap:none

include \masm32\include\windows.inc
include \masm32\include\masm32.inc
include \masm32\include\kernel32.inc
include \masm32\include\user32.inc

includelib \masm32\lib\masm32.lib
includelib \masm32\lib\kernel32.lib
includelib \masm32\lib\user32.lib

Bin2ASCII proto :DWORD,:DWORD

.data
szHexLookup db "0123456789ABCDEF"
HEX_PRE           db "%X", 32, 0 ; prefix hex, 32 for space, 0 to end
szBinaryString  db "0100100001100101011011000110110001101111" ; Hello = 48 65 6C 6C 6F
hBinarystr     db 60 dup(0)
szCapt   db "Binary To Hex", 0
.data
mybuffer db 4096 dup(?) ; total converted string
buffer   db 4096 dup(?) ; buffer

.code

start:

invoke Bin2ASCII,addr szBinaryString,addr buffer
invoke wsprintf, ADDR buffer, ADDR HEX_PRE, eax ; buffer = 5dup(0)
invoke lstrcat, ADDR mybuffer, ADDR buffer ; mybuffer db 512 dup(0)
invoke MessageBox,NULL,addr mybuffer,addr szCapt,MB_OK
Invoke ExitProcess,0
Bin2ASCII proc  sourcedata:DWORD, targetstring :DWORD


;the setup
pushad                 ;save all cpu registers

mov esi,sourcedata            ;point to source
mov edi,targetstring            ;point to destination

;mov ecx,sizeof sourcedata         ;counter into source file  PureBasic
invoke lstrlen, addr sourcedata
mov ecx, eax ; move src length to ecx

process:
lodsb
mov ah, al
and al, 0Fh
movzx edx, al
mov al, [szHexLookup + edx]
stosb

shr ah, 4
movzx edx, ah
mov al, [szHexLookup + edx]
stosb

dec ecx
jnz process
ret
popad                      ;restore all cpu registers


Bin2ASCII endp
end start



.486p
.model flat,stdcall
option casemap:none

include \masm32\include\windows.inc
include \masm32\include\masm32.inc
include \masm32\include\kernel32.inc
include \masm32\include\user32.inc

includelib \masm32\lib\masm32.lib
includelib \masm32\lib\kernel32.lib
includelib \masm32\lib\user32.lib

Bin2ASCII proto :DWORD,:DWORD

.data
HEX_PRE           db "%X", 32, 0 ; prefix hex, 32 for space, 0 to end
szBinaryString  db "0100100001100101011011000110110001101111" ; Hello = 48 65 6C 6C 6F
szCapt   db "Binary To Hex", 0
.data
mybuffer db 4096 dup(?) ; total converted string
buffer   db 4096 dup(?) ; buffer

.code

start:

invoke Bin2ASCII,addr szBinaryString,addr buffer
invoke wsprintf, ADDR buffer, ADDR HEX_PRE, eax ; buffer = 5dup(0)
invoke lstrcat, ADDR mybuffer, ADDR buffer ; mybuffer db 512 dup(0)
invoke MessageBox,NULL,addr mybuffer,addr szCapt,MB_OK
Invoke ExitProcess,0
Bin2ASCII proc  src:DWORD, dst :DWORD


;the setup
pushad                 ;save all cpu registers

mov esi,src            ;point to source
mov edi,dst            ;point to destination

;mov ecx,size        ;counter into source file  PureBasic
;mov ecx,sizeof src
invoke lstrlen, addr src
mov ecx, eax ; move src length to ecx

lea ebx,hex_table      ;get the address of the lookup table

or ecx,ecx             ;test it's not 0
jz short done

;now do the work
ALIGN 16      ;make sure the next instruction starts on a 16 byte boundary.
lp:

movzx eax,byte ptr [esi]   ;get next byte
mov edx,[4*eax+ebx]        ;look up HEX

mov [edi],dx               ;write the output
add edi,3                  ;update destination pointer
     
inc esi                    ;update pointer
dec ecx                    ;update count

jns short lp               ;go back for next character on this line

done:
ret
popad                      ;restore all cpu registers

ALIGN 16  ;make sure the lookup table is aligned in memory
hex_table:
dd "  00","  10","  20","  30","  40","  50","  60","  70"
dd "  80","  90","  A0","  B0","  C0","  D0","  E0","  F0"
dd "  01","  11","  21","  31","  41","  51","  61","  71"
dd "  81","  91","  A1","  B1","  C1","  D1","  E1","  F1"
dd "  02","  12","  22","  32","  42","  52","  62","  72"
dd "  82","  92","  A2","  B2","  C2","  D2","  E2","  F2"
dd "  03","  13","  23","  33","  43","  53","  63","  73"
dd "  83","  93","  A3","  B3","  C3","  D3","  E3","  F3"
dd "  04","  14","  24","  34","  44","  54","  64","  74"
dd "  84","  94","  A4","  B4","  C4","  D4","  E4","  F4"
dd "  05","  15","  25","  35","  45","  55","  65","  75"
dd "  85","  95","  A5","  B5","  C5","  D5","  E5","  F5"
dd "  06","  16","  26","  36","  46","  56","  66","  76"
dd "  86","  96","  A6","  B6","  C6","  D6","  E6","  F6"
dd "  07","  17","  27","  37","  47","  57","  67","  77"
dd "  87","  97","  A7","  B7","  C7","  D7","  E7","  F7"
dd "  08","  18","  28","  38","  48","  58","  68","  78"
dd "  88","  98","  A8","  B8","  C8","  D8","  E8","  F8"
dd "  09","  19","  29","  39","  49","  59","  69","  79"
dd "  89","  99","  A9","  B9","  C9","  D9","  E9","  F9"
dd "  0A","  1A","  2A","  3A","  4A","  5A","  6A","  7A"
dd "  8A","  9A","  AA","  BA","  CA","  DA","  EA","  FA"
dd "  0B","  1B","  2B","  3B","  4B","  5B","  6B","  7B"
dd "  8B","  9B","  AB","  BB","  CB","  DB","  EB","  FB"
dd "  0C","  1C","  2C","  3C","  4C","  5C","  6C","  7C"
dd "  8C","  9C","  AC","  BC","  CC","  DC","  EC","  FC"
dd "  0D","  1D","  2D","  3D","  4D","  5D","  6D","  7D"
dd "  8D","  9D","  AD","  BD","  CD","  DD","  ED","  FD"
dd "  0E","  1E","  2E","  3E","  4E","  5E","  6E","  7E"
dd "  8E","  9E","  AE","  BE","  CE","  DE","  EE","  FE"
dd "  0F","  1F","  2F","  3F","  4F","  5F","  6F","  7F"
dd "  8F","  9F","  AF","  BF","  CF","  DF","  EF","  FF"

Bin2ASCII endp
end start
Title: Re: binary to ascii
Post by: dedndave on December 22, 2012, 07:41:06 AM
if you get the string from an edit box or something, it will have a null terminator
so - no real need to keep the length
however, if you intend to test the length before converting it....
use StrLen, a masm32 library function

to do a simple test on your code, you can use the SIZEOF operator

szTest db '10101010',0

mov ecx,sizeof szTest-1    ;we use (-1) to subtract out the length of the null byte

ECX will be 8
Title: Re: binary to ascii
Post by: hfheatherfox07 on December 22, 2012, 08:16:48 AM
Thanks  dedndave...still no hex

in the mean time what divides the binary string result into 7 in this attachment ?
I want to have a long string only , no spaces

http://masm32.com/board/index.php?action=dlattach;topic=1122.0;attach=959

Thank you for your time
Title: Re: binary to ascii
Post by: jj2007 on December 22, 2012, 08:36:32 AM
Attached a console app that does conversion from Ascii to Hex and Bin and vice versa.
Usage example:

Enter empty string to exit the loop
Enter 'decode hex' or 'decode bin' to see the original strings

Text to encode = hfheatherfox07
Hex:    68 66 68 65 61 74 68 65 72 66 6F 78 30 37
Bin:    01101000 01100110 01101000 01100101 01100001 01110100 01101000 01100101
01110010 01100110 01101111 01111000 00110000 00110111

Text to encode = decode hex

Decoded from Hex=[hfheatherfox07]
Text to encode = decode bin

Decoded from Bin=[hfheatherfox07]
Text to encode =


Note you can clear the prefilled string by pressing Escape.
Title: Re: binary to ascii
Post by: hfheatherfox07 on December 22, 2012, 05:17:54 PM
How do you take out the space in between the binary string?
mov byte ptr [eax], " "   ; add a space
         inc eax

jj2007 thank you for your time  :t, but you are more advanced than me by years ..... :(
I do not get  MasmBasic
That is why for now I do examples with out it   :(
Title: Re: binary to ascii
Post by: jj2007 on December 22, 2012, 05:44:16 PM
Quote from: hfheatherfox07 on December 22, 2012, 05:17:54 PM
How do you take out the space in between the binary string?
  mov byte ptr [eax], " "   ; add a space
  inc eax
Comment out these two, and there will be no more space. But it means you need a different mechanism to decode the 1010101001010010010101001001010101001010...

QuoteI do not get  MasmBasic
Download it... (http://www.masm32.com/board/index.php?topic=94.0)
For most projects, replacing the initial includes with include \masm32\MasmBasic\MasmBasic.inc is entirely sufficient. As a bonus, you get an incredibly useful debug macro:
deb 4, "Decoding now...", $esi, eax, ecx
Shows your current string, the contents of eax and ecx, and doesn't trash anything.
QuoteThat is why for now I do examples with out it   :(
No problem. Take my examples as pseudocode showing the steps you may need to design "by hand". Of course, some stuff looks complicated because it needs to adapt to the syntax of the available function, e.g. Val():

input: 11 3f 99 0a
Val needs: 11h ->Left$("11 3f 99 0a", 2)+"h" = 11h
void Val(Cat$(Left$(ecx, 2)+"h"))

Pretty basic stuff  :biggrin:
Title: Re: binary to ascii
Post by: hfheatherfox07 on December 22, 2012, 06:45:51 PM
I found a whole bunch of conversions here in masm32
http://www.inf.unideb.hu/~fazekasg/oktatas/comparch/mintaprogramok/

How can you convert that to work with MessageBox instead of Debug view ?
I am not familiar with Debug View
Thanks
Title: Re: binary to ascii
Post by: Magnum on December 23, 2012, 05:37:45 AM
www.programmersheaven.com/mb/x86_asm/364775/364857/re-converting-binary-into-ascii/

Posted by AsmGuru62 on 22 Aug 2007 at 3:47 AM

However, it is good only for hexadecimal dumping (fastest possible code). To do binary output - loops will be needed (unless the loop completely unrolled)


;
; This macro assumes that AL has high 4 bits set to zero
; and DI points to an ASCII buffer to dump the output
; Direction flag DF=1 (forward)
;

macro AL_DIGIT_TO_HEX
{
     CMP   AL, 10
     SBB   AL, 69h
     DAS
     STOSB
}

;
; This next macro assumes that AL is a byte to dump as ASCII
; and DI points to an ASCII buffer to dump the output
; Direction flag DF=1 (forward)
;

macro AL_TO_HEX
{
    PUSH   AX
    SHR    AL, 4
    AL_DIGIT_TO_HEX

    POP    AX
    AND    AL, 0Fh
    AL_DIGIT_TO_HEX
}

;
; This next macro assumes that AX is a word to dump as ASCII
; and DI points to an ASCII buffer to dump the output
; Direction flag DF=1 (forward)
;

macro AX_TO_HEX
{
    PUSH   AX
    SHR    AX, 8
    AL_TO_HEX

    POP    AX
    AL_TO_HEX
}

;
; Now all you have to do to convert to HEX is just
; load registers and call the macro
;

buffer db 'xxxx$'

...

    MOV     AX, 0F59Bh
    MOV     DI, buffer
    CLD
    AX_TO_HEX

    MOV     DX, buffer     ; Print it to console in DOS mode
    MOV     AH, 9h
    INT     21h
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 01, 2013, 08:29:36 PM
@jj I am just looking to convert bin to ASCII text
I still can not figure out the masmbasic any way to do your example with out it?

I had a thought is there a way to write a look up table for each binary and the ASCII it represents ?
Would that be accurate ?
Like

A=01000001
a= 01100001


Etc....
Can anybody see a problem doing it that way?
Thank you
Title: Re: binary to ascii
Post by: dedndave on January 01, 2013, 09:27:20 PM
if you look at the masm32 library code (masm32\m32lib), you'll see a few routines that use LUT's
you might get some ideas - using LUT's is quite often the fastest way to do things

however, if i want to convert a binary value to ASCII binary, i use the CRT  :P
;###############################################################################################

        .XCREF
        .NoList
        INCLUDE    \Masm32\Include\Masm32rt.inc
        .List

;###############################################################################################

        .DATA?

szOutBuf db 36 dup(?)

;###############################################################################################

        .CODE

;***********************************************************************************************

_main   PROC

        INVOKE  crt__itoa,12345678h,offset szOutBuf,2
        print   offset szOutBuf,13,10
        inkey
        exit

_main   ENDP

;###############################################################################################

        END     _main

Title: Re: binary to ascii
Post by: jj2007 on January 01, 2013, 09:42:57 PM
Quote from: hfheatherfox07 on January 01, 2013, 08:29:36 PM
@jj I am just looking to convert bin to ASCII text
I still can not figure out the masmbasic any way to do your example with out it?

Sure there is a way. After all, MasmBasic is assembler ;-)
Why don't you put together the logical steps and give it a try? Once you have posted a significant amount of code, you'll surely get more help :icon14:
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 01, 2013, 09:59:28 PM
Quote from: jj2007 on January 01, 2013, 09:42:57 PM
Quote from: hfheatherfox07 on January 01, 2013, 08:29:36 PM
@jj I am just looking to convert bin to ASCII text
I still can not figure out the masmbasic any way to do your example with out it?

Sure there is a way. After all, MasmBasic is assembler ;-)
Why don't you put together the logical steps and give it a try? Once you have posted a significant amount of code, you'll surely get more help :icon14:

Thanks I will give it another shot ,I appreciate it
It seems shorter when you use masmbasic ....
I notice a lot of your code is really short
Once I tried to just add the functions without the lib it got large


Title: Re: binary to ascii
Post by: dedndave on January 02, 2013, 05:13:30 AM
here, Heather, i will get you started.....
;###############################################################################################

        .XCREF
        .NoList
        INCLUDE    \Masm32\Include\Masm32rt.inc
        .List

;###############################################################################################

Char2AscBin PROTO :DWORD,:LPVOID

;###############################################################################################

        .DATA

szString  db 'Hello Heather',0

;***********************************************************************************************

        .DATA?

szBuffer db 9 dup(?)

;###############################################################################################

        .CODE

;***********************************************************************************************

_main   PROC

        mov     esi,offset szString
        mov     edi,offset szBuffer
        jmp short Loop01

Loop00: INVOKE  Char2AscBin,eax,edi
        print   edi,32

Loop01: lodsb
        or      al,al
        jnz     Loop00

        print   chr$(13,10)
        inkey
        exit

_main   ENDP

;***********************************************************************************************

Char2AscBin PROC USES EDI dwChar:DWORD,lpBuffer:LPVOID

        mov     edx,dwChar
        mov     al,30h
        mov     edi,lpBuffer
        bswap   edx
        mov     ecx,8

ChAsc0: shr     eax,1
        shl     edx,1
        rcl     eax,1
        dec     ecx
        stosb
        jnz     ChAsc0

        xchg    eax,ecx
        stosb
        ret

Char2AscBin ENDP

;###############################################################################################

        END     _main
Title: Re: binary to ascii
Post by: dedndave on January 02, 2013, 06:15:23 AM
that one was a console version
this one uses a MessageBox...
;###############################################################################################

        .XCREF
        .NoList
        INCLUDE    \Masm32\Include\Masm32rt.inc
        .List

;###############################################################################################

Char2AscBin PROTO :DWORD,:LPSTR
Sz2AscBin   PROTO :LPSTR,:LPSTR

;###############################################################################################

        .DATA

szString  db 'Hello Heather',0

;***********************************************************************************************

        .DATA?

szBuffer db 9*(sizeof szString-1) dup(?)

;###############################################################################################

        .CODE

;***********************************************************************************************

_main   PROC

        mov     edi,offset szBuffer
        mov     esi,offset szString
        INVOKE  Sz2AscBin,esi,edi
        INVOKE  MessageBox,HWND_DESKTOP,edi,esi,MB_OK
        exit

_main   ENDP

;***********************************************************************************************

Char2AscBin PROC USES EDI dwChar:DWORD,lpBuffer:LPSTR

        mov     edx,dwChar
        mov     al,30h
        mov     edi,lpBuffer
        bswap   edx
        mov     ecx,8

ChAsc0: shr     eax,1
        shl     edx,1
        rcl     eax,1
        dec     ecx
        stosb
        jnz     ChAsc0

        xchg    eax,ecx
        stosb
        ret

Char2AscBin ENDP

;***********************************************************************************************

Sz2AscBin PROC USES ESI EDI lpSrc:LPSTR,lpDest:LPSTR

        mov     esi,lpSrc
        mov     edi,lpDest
        jmp short SzAsc1

SzAsc0: INVOKE  Char2AscBin,eax,edi
        add     edi,8
        mov     al,32
        stosb

SzAsc1: lodsb
        or      al,al
        jnz     SzAsc0

        dec     edi
        stosb
        ret

Sz2AscBin ENDP

;###############################################################################################

        END     _main
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 02, 2013, 06:21:01 AM
thanks dedndave,
I am trying to do the opposite ...I have that , I posted a tool for that a couple posts up
2nd page 6 post down http://masm32.com/board/index.php?action=dlattach;topic=1122.0;attach=959
also I was trying to take out the spaces in between the binary text out put
That is why I am am thinking  a LUT 
Title: Re: binary to ascii
Post by: dedndave on January 02, 2013, 06:24:08 AM
no need to "take out the spaces", per se
just skip over them as you translate
more precisely, use them to indicate a new ASCII char   :P

but - you still haven't established a set of rules for conversion
we are waiting, patiently - lol

i would say an LUT is overkill for this purpose
but - according to Hutch, size doesn't matter (probably has something to do with being single)
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 02, 2013, 06:29:29 AM
I meant spaces in the result so It looks like this :
01001000011001010110110001101100011011110010000001001000011001010110000101110100011010000110010101110010

Also when using this http://www.roubaixinteractive.com/PlayGround/Binary_Conversion/Binary_To_Text.asp
I noticed that it does not matter weather you input the above binary with the spaces or a continues string , you still get the right ASCII result!
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 02, 2013, 06:35:50 AM
Quote from: dedndave on January 01, 2013, 09:27:20 PM
if you look at the masm32 library code (masm32\m32lib), you'll see a few routines that use LUT's
you might get some ideas - using LUT's is quite often the fastest way to do things


Thanks I found 2 LUT,s right off the top ....
argbynum.asm  and ascdump.asm
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 02, 2013, 06:44:45 AM
What is bintbl.asm used for ?
Title: Re: binary to ascii
Post by: Donkey on January 02, 2013, 06:50:36 AM
If all you want to do is strip out spaces simply copy the string over itself skipping over the space character

StripSpaces FRAME pszString
uses edi,esi

// copy the string 1 byte at a time
mov edi,[pszString]
mov esi,[pszString]
:
mov al,[edi]
cmp al," "
je >.SKIP
mov [esi],al
inc esi
.SKIP
inc edi
cmp al,0
jne <

ret
endf


The string will have all spaces removed.
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 02, 2013, 06:53:29 AM
Thank You Donkey!!  :t
I was looking for something like that
Title: Re: binary to ascii
Post by: dedndave on January 02, 2013, 06:55:35 AM
bintbl.asm...
the public symbol is "bintable"
use explorer search tool
look for files in masm32\m32lib containing "bintable"   :P

i get...
b2b_ex.asm
dw2b_ex.asm
w2b_ex.asm
Title: Re: binary to ascii
Post by: Donkey on January 02, 2013, 06:56:04 AM
No problem hfheatherfox07, I changed the post to include the full procedure I used to test it with.
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 02, 2013, 07:31:02 AM
For some odd reason it is not working for me ?


;###############################################################################################

        .XCREF
        .NoList
        INCLUDE    \Masm32\Include\Masm32rt.inc
        .List

;###############################################################################################

Char2AscBin PROTO :DWORD,:LPSTR
Sz2AscBin   PROTO :LPSTR,:LPSTR
StripSpaces PROTO :DWORD,:DWORD
;###############################################################################################

        .DATA

szString  db 'Hello Heather',0

;***********************************************************************************************

        .DATA?

szBuffer db 9*(sizeof szString-1) dup(?)
szNewString dd ?
mybuffer dd ?
;###############################################################################################

        .CODE

;***********************************************************************************************

_main   PROC

        mov     edi,offset szBuffer
        mov     esi,offset szString
        INVOKE  Sz2AscBin,esi,edi
        invoke lstrcat, addr mybuffer,edi
        INVOKE  StripSpaces,addr mybuffer,addr szNewString
        INVOKE  MessageBox,HWND_DESKTOP,addr szNewString,esi,MB_OK
        exit

_main   ENDP

;***********************************************************************************************

Char2AscBin PROC USES EDI dwChar:DWORD,lpBuffer:LPSTR

        mov     edx,dwChar
        mov     al,30h
        mov     edi,lpBuffer
        bswap   edx
        mov     ecx,8

ChAsc0: shr     eax,1
        shl     edx,1
        rcl     eax,1
        dec     ecx
        stosb
        jnz     ChAsc0

        xchg    eax,ecx
        stosb
        ret

Char2AscBin ENDP

;***********************************************************************************************

Sz2AscBin PROC USES ESI EDI lpSrc:LPSTR,lpDest:LPSTR

        mov     esi,lpSrc
        mov     edi,lpDest
        jmp short SzAsc1

SzAsc0: INVOKE  Char2AscBin,eax,edi
        add     edi,8
        mov     al,32
        stosb

SzAsc1: lodsb
        or      al,al
        jnz     SzAsc0

        dec     edi
        stosb
        ret

Sz2AscBin ENDP

;###############################################################################################
StripSpaces Proc uses edi esi pszString:DWORD ,pNewString:DWORD


; copy the string 1 byte at a time
mov edi,[pszString]
mov esi,[pNewString]

mov al,[edi]
cmp al," "
je SKIP
mov [esi],al
inc esi
SKIP:
inc edi
cmp al,0
jne SKIP

ret
StripSpaces endp
END     _main

Title: Re: binary to ascii
Post by: dedndave on January 02, 2013, 07:33:25 AM
your buffers are too small
szNewString dd ?
mybuffer dd ?

those are both 4 bytes long   :P
Title: Re: binary to ascii
Post by: Donkey on January 02, 2013, 07:42:57 AM
You mistranslated the code I posted as well, should be:

StripSpaces Proc uses edi esi pszString:DWORD ,pNewString:DWORD

; copy the string 1 byte at a time
mov edi,[pszString]
mov esi,[pNewString]

TOPOFLOOP:
mov al,[edi]
cmp al," "
je SKIP
mov [esi],al
inc esi
SKIP:
inc edi
cmp al,0
jne TOPOFLOOP

ret
StripSpaces endp
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 02, 2013, 07:50:32 AM
Ya that did it  Donkey  :t...I was wondering why I am looping at the end back to       inc edi
      cmp al,0

Your StripSpaces Proc is a nice proc to have .... Thank you!  :biggrin:


;###############################################################################################

        .XCREF
        .NoList
        INCLUDE    \Masm32\Include\Masm32rt.inc
        .List

;###############################################################################################

Char2AscBin PROTO :DWORD,:LPSTR
Sz2AscBin   PROTO :LPSTR,:LPSTR
StripSpaces PROTO :DWORD,:DWORD
;###############################################################################################

        .DATA

szString  db 'Hello Heather',0

;***********************************************************************************************

        .DATA?

szBuffer db 9*(sizeof szString-1) dup(?)
szNewString db 4096 dup(?)
szMybuffer db 4096 dup(?)
;###############################################################################################

        .CODE

;***********************************************************************************************

_main   PROC

        mov     edi,offset szBuffer
        mov     esi,offset szString
        INVOKE  Sz2AscBin,esi,edi
        invoke lstrcat, addr szMybuffer,edi
        INVOKE  StripSpaces,addr szMybuffer,addr szNewString
        INVOKE  MessageBox,HWND_DESKTOP,addr szNewString,esi,MB_OK
        exit

_main   ENDP

;***********************************************************************************************

Char2AscBin PROC USES EDI dwChar:DWORD,lpBuffer:LPSTR

        mov     edx,dwChar
        mov     al,30h
        mov     edi,lpBuffer
        bswap   edx
        mov     ecx,8

ChAsc0: shr     eax,1
        shl     edx,1
        rcl     eax,1
        dec     ecx
        stosb
        jnz     ChAsc0

        xchg    eax,ecx
        stosb
        ret

Char2AscBin ENDP

;***********************************************************************************************

Sz2AscBin PROC USES ESI EDI lpSrc:LPSTR,lpDest:LPSTR

        mov     esi,lpSrc
        mov     edi,lpDest
        jmp short SzAsc1

SzAsc0: INVOKE  Char2AscBin,eax,edi
        add     edi,8
        mov     al,32
        stosb

SzAsc1: lodsb
        or      al,al
        jnz     SzAsc0

        dec     edi
        stosb
        ret

Sz2AscBin ENDP

;###############################################################################################
StripSpaces Proc uses edi esi pszString:DWORD ,pNewString:DWORD

; copy the string 1 byte at a time
mov edi,[pszString]
mov esi,[pNewString]

TOPOFLOOP:
mov al,[edi]
cmp al," "
je SKIP
mov [esi],al
inc esi
SKIP:
inc edi
cmp al,0
jne TOPOFLOOP

ret
StripSpaces endp
END     _main

Title: Re: binary to ascii
Post by: Donkey on January 02, 2013, 08:16:52 AM
Quote from: hfheatherfox07 on January 02, 2013, 07:50:32 AM
Your StripSpaces Proc is a nice proc to have .... Thank you!  :biggrin:

Glad to help
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 02, 2013, 05:46:00 PM
OK
Back to my original question I am trying to convert Binary text to ASCII
I think the only way to do this is with a look up table
but every time i try to write a look up table I get errors !!
any body know how to write this table ?
It should have 255 entries like  "StringTable" in ascdump.asm from m32lib since The extended ASCII table has 255 entries   http://www.ascii-code.com/   or maybe less

How do I represent for example that 01000001 = A and that 01100001 = a  ?

Thank you !
Title: Re: binary to ascii
Post by: MichaelW on January 02, 2013, 06:03:45 PM
I still don't understand what you are asking, but perhaps it will help if I point out that 01000001b is the ASCII character code for "A", 01000010b the ASCII character code for "B", etc, and that characters are normally specified by their character code. So for example the string "ABC" would be stored as three bytes: 01000001b, 01000010b, 01000011b
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 02, 2013, 06:33:56 PM
I am trying to make a look up table to convert :
01001000 01100101 01101100 01101100 01101111 00100000 01010111 01101111 01110010 01101100 01100100
To: Hello World

Title: Re: binary to ascii
Post by: MichaelW on January 02, 2013, 06:48:58 PM
Is this a string of binary digits?

01001000 01100101 01101100 01101100 01101111 00100000 01010111 01101111 01110010 01101100 01100100

Or a binary representation of 11 bytes?
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 02, 2013, 06:57:31 PM
Quote from: MichaelW on January 02, 2013, 06:48:58 PM
Is this a string of binary digits?

01001000 01100101 01101100 01101100 01101111 00100000 01010111 01101111 01110010 01101100 01100100

Or a binary representation of 11 bytes?

I am trying to make an app that converts like this http://www.roubaixinteractive.com/PlayGround/Binary_Conversion/Binary_To_Text.asp

So what ever that is

Title: Re: binary to ascii
Post by: hfheatherfox07 on January 02, 2013, 07:13:43 PM
This is what I had in mind , except it is not working

.486p
.model flat,stdcall
option casemap:none

include \masm32\include\windows.inc
include \masm32\include\masm32.inc
include \masm32\include\kernel32.inc
include \masm32\include\user32.inc

includelib \masm32\lib\masm32.lib
includelib \masm32\lib\kernel32.lib
includelib \masm32\lib\user32.lib

Bin2ASCII proto :DWORD,:DWORD

.data
szBinaryLookup db 01000001b,01000010b,01000011b
format db "%x",0
szBinaryString  db "010000010100001001000011" ; ABC
mybuffer db 4096 dup(?) ; total converted string
buffer   db 4096 dup(?) ; buffer
szCapt   db "Binary To ASCII text", 0
.code

start:

invoke Bin2ASCII,addr szBinaryString,addr buffer
invoke wsprintf, ADDR buffer, ADDR format, edi
invoke lstrcat, ADDR mybuffer, ADDR buffer
invoke MessageBox,NULL,addr buffer,addr szCapt,MB_OK
Invoke ExitProcess,0
Bin2ASCII proc  src:DWORD, dst :DWORD



pushad                 ;save all cpu registers

mov esi,src            ;point to source
mov edi,dst            ;point to destination

mov ecx, sizeof szBinaryString - 1
Convert:
lodsb
mov ah, al
and al, 0FFh
movzx edx, al
mov al, [szBinaryLookup + edx]
stosb

shr ah, 4
movzx edx, ah
mov al, [szBinaryLookup + edx]
stosb

dec ecx
jnz Convert

ret
popad
Bin2ASCII endp

end start
Title: Re: binary to ascii
Post by: Donkey on January 02, 2013, 07:33:16 PM
ScanBytes FRAME pszString,pBuffer
uses edi,esi

// scan 8 bits at a time
xor ecx,ecx
mov edi,[pszString]
mov esi,[pBuffer]

.NEWBYTE
mov B[esi],0
mov ecx,7
.SETBYTE
mov al,[edi]
cmp al,"1"
jne >.SKIP
bts [esi],cx
.SKIP
inc edi
dec ecx
jns <.SETBYTE
inc esi
mov al,[edi]
test al,al
jnz <.NEWBYTE

ret
endf


Be sure to strip the spaces before you run it through the grinder.

My output for your string was

Line 50: Output = Hello World

EDIT:

This is my attempt at translating to MASM, should work but might need some correcting

ScanBytes PROC uses edi esi pszString:DWORD,pBuffer:DWORD
xor ecx,ecx
mov edi,[pszString]
mov esi,[pBuffer]

NEWBYTE:
mov BYTE PTR [esi],0
mov ecx,7
SETBYTE:
mov al,[edi]
cmp al,49
jne SKIP
bts [esi],cx
SKIP:
inc edi
dec ecx
jns SETBYTE
inc esi
mov al,[edi]
test al,al
jnz NEWBYTE
ret
ENDP
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 02, 2013, 07:46:19 PM
@Donkey I am not sure how you intended that ?
.486p
.model flat,stdcall
option casemap:none

include \masm32\include\windows.inc
include \masm32\include\masm32.inc
include \masm32\include\kernel32.inc
include \masm32\include\user32.inc

includelib \masm32\lib\masm32.lib
includelib \masm32\lib\kernel32.lib
includelib \masm32\lib\user32.lib

ScanBytes proto :DWORD,:DWORD

.data
szCapt   db "Binary To ASCII text", 0
szBinaryLookup db 01000001b,01000010b,01000011b
format db "%x",0
szBinaryString  db "010000010100001001000011" ; ABC  010000010100001001000011 or  01000001 01000010 01000011
.data?
mybuffer db 4096 dup(?) ; total converted string
buffer   db 4096 dup(?) ; buffer
B dd ?
.code

start:

invoke ScanBytes,addr szBinaryString,addr buffer
invoke wsprintf, ADDR buffer, ADDR format, esi
invoke lstrcat, ADDR mybuffer, ADDR buffer
invoke MessageBox,NULL,addr mybuffer,addr szCapt,MB_OK
Invoke ExitProcess,0

ScanBytes PROC uses edi esi pszString:DWORD,pBuffer:DWORD
xor ecx,ecx
mov edi,[pszString]
mov esi,[pBuffer]

NEWBYTE:
mov BYTE PTR [esi],0
mov ecx,7
SETBYTE:
mov al,[edi]
cmp al,49
jne SKIP
bts [esi],cx
SKIP:
inc edi
dec ecx
jns SETBYTE
inc esi
mov al,[edi]
test al,al
jnz NEWBYTE
ret

ScanBytes endp

end start
Title: Re: binary to ascii
Post by: Donkey on January 02, 2013, 07:51:41 PM
Hi,

I saw the link in your post above and thought you were trying to convert binary represented as a string of 0 and 1 characters into useable ascii text. For example the message in your link (http://www.roubaixinteractive.com/PlayGround/Binary_Conversion/Binary_To_Text.asp) decodes as:

Be sure to drink your Ovaltine.

In order to execute the routine, use the following:

invoke StripSpaces,offset String1,offset StringOut
invoke ScanBytes,offset StringOut,offset Output


Works like a charm here.
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 02, 2013, 07:58:43 PM
Yap I made an error trying to format it  ::)

It works like a charm!!!!  :greenclp:
I translate Perfect!!!
Thanks Donkey  :biggrin:

I took the Binary Message that site had and it converted it Perfect !!!

.486p
.model flat,stdcall
option casemap:none

include \masm32\include\windows.inc
include \masm32\include\masm32.inc
include \masm32\include\kernel32.inc
include \masm32\include\user32.inc

includelib \masm32\lib\masm32.lib
includelib \masm32\lib\kernel32.lib
includelib \masm32\lib\user32.lib

ScanBytes proto :DWORD,:DWORD

.data
szCapt   db "Binary To ASCII text", 0

StringOut  db "01000010011001010010000001110011011101010111001001100101001000000111010001101111001000000110010001110010011010010110111001101011001000000111100101101111011101010111001000100000010011110111011001100001011011000111010001101001011011100110010100101110"
.data?

Output   db 4096 dup(?) ; total converted string buffer

.code

start:


invoke ScanBytes,offset StringOut,offset Output
invoke MessageBox,NULL,addr Output,addr szCapt,MB_OK
Invoke ExitProcess,0

ScanBytes PROC uses edi esi pszString:DWORD,pBuffer:DWORD
xor ecx,ecx
mov edi,[pszString]
mov esi,[pBuffer]

NEWBYTE:
mov BYTE PTR [esi],0
mov ecx,7
SETBYTE:
mov al,[edi]
cmp al,49
jne SKIP
bts [esi],cx
SKIP:
inc edi
dec ecx
jns SETBYTE
inc esi
mov al,[edi]
test al,al
jnz NEWBYTE
ret

ScanBytes endp

end start
Title: Re: binary to ascii
Post by: Donkey on January 02, 2013, 08:02:11 PM
Quote from: hfheatherfox07 on January 02, 2013, 07:58:43 PM
Thanks Donkey  :biggrin:

Any time, it was an interesting problem. Hockey is about to start, damn those Russians for not living in a decent time zone. Anyway USA vs Czech Republic so I'm shutting it down...
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 02, 2013, 08:03:29 PM
4:03  AM Here
Can't Sleep LOL
Title: Re: binary to ascii
Post by: Donkey on January 02, 2013, 08:07:01 PM
Quote from: hfheatherfox07 on January 02, 2013, 08:03:29 PM
4:03  AM Here
Can't Sleep LOL

Should have drank your Ovaltine  :biggrin:
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 02, 2013, 08:10:33 PM
 That was too Funny
:lol:
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 02, 2013, 08:12:58 PM
Here is my Problem :
Tim Hortons Take Home Coffee

(http://ecx.images-amazon.com/images/I/21YOjluI9vL._SX270_.jpg)

3 mugs in the morning
2 mugs in the afternoon
2 mugs in the evening

Stuff is addictive 
Title: Re: binary to ascii
Post by: dedndave on January 03, 2013, 03:49:53 AM
think i have a little bug   :P

(http://img9.imageshack.us/img9/5948/heather0.png)
Title: Re: binary to ascii
Post by: Donkey on January 03, 2013, 04:44:27 AM
Quote from: hfheatherfox07 on January 02, 2013, 08:12:58 PM
Here is my Problem :
Tim Hortons Take Home Coffee

(http://ecx.images-amazon.com/images/I/21YOjluI9vL._SX270_.jpg)

3 mugs in the morning
2 mugs in the afternoon
2 mugs in the evening

Stuff is addictive

Just woke up after staying up till nearly 5am watching the US kick the Czech Republic's arse. Had a buddy who drove a semi for Timmy's, used to get cases of coffee for free. The stuff is the crack cocaine of coffee, I'm completely at it's mercy.

Quote from: dedndave on January 03, 2013, 03:49:53 AM
think i have a little bug   :P

(http://img9.imageshack.us/img9/5948/heather0.png)

Weird, I didn't have any problems with it here at all.
Title: Re: binary to ascii
Post by: dedndave on January 03, 2013, 04:56:31 AM
i am writing my own - lol
this is what i'm using for a test string...
szTest      db '1001000 1100101 1101100 1101100 01101111 100000 01001000011001010110000101110100011010000110010101110010',0

might be the leading 0 - i will play with it, later
Title: Re: binary to ascii
Post by: jj2007 on January 03, 2013, 05:53:42 AM
Dave,
01001000011001010110000101110100011010000110010101110010 is a 56-bit sequence - how do you want it to be interpreted?
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 03, 2013, 08:01:02 AM
Quote from: dedndave on January 03, 2013, 04:56:31 AM
i am writing my own - lol
this is what i'm using for a test string...
szTest      db '1001000 1100101 1101100 1101100 01101111 100000 01001000011001010110000101110100011010000110010101110010',0

might be the leading 0 - i will play with it, later

@dedndave
I think I am starting to understand this a little ....as MichaelW posted here http://masm32.com/board/index.php?PHPSESSID=417435d04dc4625d2de9d4f3ae67b9a1&topic=1122.45

01000001b is the ASCII character code for "A", 01000010b the ASCII character code for "B", etc....
as I found here http://www.ascii-code.com/

Remember that question you asked me about defining a rule  and I had no idea how to answer ?
I think that is the rule as MichaelW stated , That is just how they are represented
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 03, 2013, 01:57:29 PM
I realize that we have a solution by Donkey ....
But I still would like to make a version that decodes binary ASCII string using a Look Up Table ...
Now that MichaelW  explained how Characters are represented in Binary I thought it should be easy ,
But I am Getting an empty result , I have no experience with LUT'S Does any body know why I am not Showing  'ABC' ?
010000010100001001000011 Should give ABC answer !
I put ebx in the result so you can see that it is looking up the table and it is giving 'A' the fiest value in the table
invoke MessageBox,NULL, ebx,addr szCapt,MB_OK
I know it should be
invoke MessageBox,NULL, addr mybuffer,addr szCapt,MB_OK

Also I have modified the first three entries in a hex table as it is time consuming and until I can get this to work I did not want to spend too much time make a full table

Thank You !

.486p
.model flat,stdcall
option casemap:none

include \masm32\include\windows.inc
include \masm32\include\masm32.inc
include \masm32\include\kernel32.inc
include \masm32\include\user32.inc

includelib \masm32\lib\masm32.lib
includelib \masm32\lib\kernel32.lib
includelib \masm32\lib\user32.lib

Bin2ASCII proto :DWORD,:DWORD

.data
szCapt   db "Binary To ASCII", 0
szBinaryString  db "010000010100001001000011" ; ABC
.data?
mybuffer db 4096 dup(?) ; total converted string
buffer   db 4096 dup(?) ; buffer

.code

start:

invoke Bin2ASCII,addr szBinaryString,addr buffer
invoke lstrcat, addr mybuffer, addr buffer
invoke MessageBox,NULL, ebx,addr szCapt,MB_OK
Invoke ExitProcess,0
Bin2ASCII proc  uses edi esi pszString:DWORD,pBuffer:DWORD


pushad                 ;save all cpu registers
xor ecx,ecx
mov edi,[pszString]    ;point to source
mov esi,[pBuffer] ;point to destination
   
mov ecx,sizeof  szBinaryString -1 ; movec ounter length to ecx


lea ebx,Binary_table      ;get the address of the lookup table

test ecx,ecx             ;test it's not 0
jz short done

;now do the work
ALIGN 16      ;make sure the next instruction starts on a 16 byte boundary.
lop:

movzx eax,byte ptr [esi]   ;get next byte
mov edx,[4*eax+ebx]        ;look up Binary

mov [edi],dx               ;write the output
add edi,3                  ;update destination pointer
     
inc esi                    ;update pointer
dec ecx                    ;update count

jns short lop               ;go back for next character on this line

done:
xor eax, eax
ret
popad                      ;restore all cpu registers

ALIGN 16  ;make sure the lookup table is aligned in memory
Binary_table:
;01000001b = A 01000010 = B 01000011 = C
dd  01000001b,01000010b,01000011b,"  30","  40","  50","  60","  70"
dd "  80","  90","  A0","  B0","  C0","  D0","  E0","  F0"
dd "  01","  11","  21","  31","  41","  51","  61","  71"
dd "  81","  91","  A1","  B1","  C1","  D1","  E1","  F1"
dd "  02","  12","  22","  32","  42","  52","  62","  72"
dd "  82","  92","  A2","  B2","  C2","  D2","  E2","  F2"
dd "  03","  13","  23","  33","  43","  53","  63","  73"
dd "  83","  93","  A3","  B3","  C3","  D3","  E3","  F3"
dd "  04","  14","  24","  34","  44","  54","  64","  74"
dd "  84","  94","  A4","  B4","  C4","  D4","  E4","  F4"
dd "  05","  15","  25","  35","  45","  55","  65","  75"
dd "  85","  95","  A5","  B5","  C5","  D5","  E5","  F5"
dd "  06","  16","  26","  36","  46","  56","  66","  76"
dd "  86","  96","  A6","  B6","  C6","  D6","  E6","  F6"
dd "  07","  17","  27","  37","  47","  57","  67","  77"
dd "  87","  97","  A7","  B7","  C7","  D7","  E7","  F7"
dd "  08","  18","  28","  38","  48","  58","  68","  78"
dd "  88","  98","  A8","  B8","  C8","  D8","  E8","  F8"
dd "  09","  19","  29","  39","  49","  59","  69","  79"
dd "  89","  99","  A9","  B9","  C9","  D9","  E9","  F9"
dd "  0A","  1A","  2A","  3A","  4A","  5A","  6A","  7A"
dd "  8A","  9A","  AA","  BA","  CA","  DA","  EA","  FA"
dd "  0B","  1B","  2B","  3B","  4B","  5B","  6B","  7B"
dd "  8B","  9B","  AB","  BB","  CB","  DB","  EB","  FB"
dd "  0C","  1C","  2C","  3C","  4C","  5C","  6C","  7C"
dd "  8C","  9C","  AC","  BC","  CC","  DC","  EC","  FC"
dd "  0D","  1D","  2D","  3D","  4D","  5D","  6D","  7D"
dd "  8D","  9D","  AD","  BD","  CD","  DD","  ED","  FD"
dd "  0E","  1E","  2E","  3E","  4E","  5E","  6E","  7E"
dd "  8E","  9E","  AE","  BE","  CE","  DE","  EE","  FE"
dd "  0F","  1F","  2F","  3F","  4F","  5F","  6F","  7F"
dd "  8F","  9F","  AF","  BF","  CF","  DF","  EF","  FF"

Bin2ASCII endp
end start

Title: Re: binary to ascii
Post by: hfheatherfox07 on January 03, 2013, 05:59:25 PM
I took the time to complete the whole Binary table ...
Still No Go  :(
I would appropriate any help
Thank you !

.486p
.model flat,stdcall
option casemap:none

include \masm32\include\windows.inc
include \masm32\include\masm32.inc
include \masm32\include\kernel32.inc
include \masm32\include\user32.inc

includelib \masm32\lib\masm32.lib
includelib \masm32\lib\kernel32.lib
includelib \masm32\lib\user32.lib

Bin2ASCII proto :DWORD,:DWORD,:DWORD

.data
szCapt   db "Binary To ASCII", 0
szBinaryString  db "010000010100001001000011" ; ABC
.data?
mybuffer db 4096 dup(?) ; total converted string
buffer   db 4096 dup(?) ; buffer

.code

start:

invoke Bin2ASCII,addr szBinaryString,addr buffer,sizeof szBinaryString-1
invoke lstrcat, addr mybuffer, addr buffer
invoke MessageBox,NULL,addr mybuffer ,addr szCapt,MB_OK
Invoke ExitProcess,0
Bin2ASCII proc   sourcedata:DWORD, targetstring:DWORD, sourcelength:DWORD



pushad                 ;save all cpu registers

mov esi, [sourcedata]  ;point to source
mov edi, [targetstring]  ;point to destination
mov ecx, [sourcelength]   ;counter into source file


lea ebx,Binary_table      ;get the address of the lookup table

or ecx,ecx             ;test it's not 0
jz short done

;now do the work
ALIGN 16      ;make sure the next instruction starts on a 16 byte boundary.
lop:

movzx eax,byte ptr [esi]   ;get next byte
mov edx,[4*eax+ebx]        ;look up Binary

mov [edi],dx               ;write the output
add edi,3                  ;update destination pointer
     
inc esi                    ;update pointer
dec ecx                    ;update count

jns short lop               ;go back for next character on this line

done:

ret
popad                      ;restore all cpu registers
;all done, now the answer is in the buffer pointed to by destination [edi]
ALIGN 16  ;make sure the lookup table is aligned in memory
Binary_table:

dd  00000000b,00000001b,00000010b,00000011b,00000100b,00000101b,00000110b,00000111b
dd  00001000b,00001001b,00001010b,00001011b,00001100b,00001101b,00001110b,00001111b
dd  00010000b,00010001b,00010010b,00010011b,00010100b,00010101b,00010110b,00010111b
dd  00011000b,00011001b,00011010b,00011011b,00011100b,00011101b,00011110b,00011111b
dd  00100000b,00100001b,00100010b,00100011b,00100100b,00100101b,00100110b,00100111b
dd  00101000b,00101001b,00101010b,00101011b,00101100b,00101101b,00101110b,00101111b
dd  00110000b,00110001b,00110010b,00110011b,00110100b,00110101b,00110110b,00110111b
dd  00111000b,00111001b,00111010b,00111011b,00111100b,00111101b,00111110b,00111111b
dd  01000000b,01000001b,01000010b,01000011b,01000100b,01000101b,01000110b,01000111b
dd  01001000b,01001001b,01001010b,01001011b,01001100b,01001101b,01001110b,01001111b
dd  01010000b,01010001b,01010010b,01010011b,01010100b,01010101b,01010110b,01010111b
dd  01011000b,01011001b,01011010b,01011011b,01011100b,01011101b,01011110b,01011111b
dd  01100000b,01100001b,01100010b,01100011b,01100100b,01100101b,01100110b,01100111b
dd  01101000b,01101001b,01101010b,01101011b,01101100b,01101101b,01101110b,01101111b
dd  01110000b,01110001b,01110010b,01110011b,01110100b,01110101b,01110110b,01110111b
dd  01111000b,01111001b,01111010b,01111011b,01111100b,01111101b,01111110b,01111111b
dd  10000000b,10000001b,10000010b,10000011b,10000100b,10000101b,10000110b,10000111b
dd  10001000b,10001001b,10001010b,10001011b,10001100b,10001101b,10001110b,10001111b 
dd  10010000b,10010001b,10010010b,10010011b,10010100b,10010101b,10010110b,10010111b
dd  10011000b,10011001b,10011010b,10011011b,10011100b,10011101b,10011110b,10011111b
dd  10100000b,10100001b,10100010b,10100011b,10100100b,10100101b,10100110b,10100111b
dd  10101000b,10101001b,10101010b,10101011b,10101100b,10101101b,10101110b,10101111b
dd  10110000b,10110001b,10110010b,10110011b,10110100b,10110101b,10110110b,10110111b
dd  10111000b,10111001b,10111010b,10111011b,10111100b,10111101b,10111110b,10111111b
dd  11000000b,11000001b,11000010b,11000011b,11000100b,11000101b,11000110b,11000111b
dd  11001000b,11001001b,11001010b,11001011b,11001100b,11001101b,11001110b,11001111b
dd  11010000b,11010001b,11010010b,11010011b,11010100b,11010101b,11010110b,11010111b
dd  11011000b,11011001b,11011010b,11011011b,11011100b,11011101b,11011110b,11011111b
dd  11100000b,11100001b,11100010b,11100011b,11100100b,11100101b,11100110b,11100111b
dd  11101000b,11101001b,11101010b,11101011b,11101100b,11101101b,11101110b,11101111b
dd  11110000b,11110001b,11110010b,11110011b,11110100b,11110101b,11110110b,11110111b
dd  11111000b,11111001b,11111010b,11111011b,11111100b,11111101b,11111110b,11111111b

Bin2ASCII endp
end start
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 03, 2013, 06:24:42 PM
Looking at argbynum.asm from masm32\m32lib for reference ...
Am I writing my table right ?

when should I use   dd as oppose to db ALIGN 16 as oppose ALIGN 4 ?

:(

Title: Re: binary to ascii
Post by: Dubby on January 03, 2013, 07:19:54 PM
what about building tiny tables...?  ;)  :badgrin: :idea: :idea:

grab the logic here: http://www.wikihow.com/Convert-Binary-to-Hexadecimal 


.486p
.model flat,stdcall
option casemap:none

include \masm32\include\windows.inc
include \masm32\include\masm32.inc
include \masm32\include\kernel32.inc
include \masm32\include\user32.inc

includelib \masm32\lib\masm32.lib
includelib \masm32\lib\kernel32.lib
includelib \masm32\lib\user32.lib

BinaryToACSII proto input:LPDWORD, output:LPDWORD
RetrieveHexValueFromTable proto input:LPDWORD
RetrieveHexValue proto input:LPDWORD

.data?

.data

szTest db "01001000011001010110110001101100011011110010000001001000011001010110000101110100011010000110010101110010",0
Output db 4096 dup(?)
.code
start:
invoke BinaryToACSII, Addr szTest, Addr Output
Invoke MessageBox,NULL, Addr Output, NULL, MB_OK
invoke ExitProcess,NULL


BinaryToACSII proc uses esi edi ebx input:LPDWORD, output:LPDWORD
; STRICT rules:
; binary lenght must be able to be divided by 8


local len:DWORD


local lpStrTemp[4]:DWORD

mov esi, input
mov edi, output
invoke lstrlen, esi
mov len, eax
mov ecx, eax
mov ebx, 8
cdq
div ebx

.if (edx)
.data
MalformerdBin db "Malformed Binary string",13,"Binary lenght must be able to be divided by 8",0
.code
Invoke MessageBox, NULL, Addr MalformerdBin, NULL, MB_OK
ret
.endif
mov Ebx, len

.while  Ebx > 0
invoke RtlZeroMemory, Addr lpStrTemp, sizeof lpStrTemp
Invoke MemCopy, esi, Addr lpStrTemp, 8
Invoke RetrieveHexValue, Addr lpStrTemp
Mov Byte ptr [edi], AL
Inc Edi
Add Esi, 8
Sub Ebx, 8
.endw
ret
BinaryToACSII endp

RetrieveHexValue proc uses esi edi input:LPDWORD
local String[2]:DWORD

Mov esi, input
Invoke RtlZeroMemory, Addr String, sizeof String
Invoke MemCopy, esi, Addr String, 4
Invoke RetrieveHexValueFromTable, Addr String
Mov Edi, Eax
Shl Edi, 4
Add Esi, 4
Invoke MemCopy, esi, Addr String, 4
Invoke RetrieveHexValueFromTable, Addr String
Or Edi, Eax
Mov Eax, Edi
ret
RetrieveHexValue endp

RetrieveHexValueFromTable Proc uses esi ebx input:LPDWORD

mov esi, OFFSET hextables
; ebx counter
xor ebx, ebx
Dec Ebx
xor eax, eax
inc eax
.while (eax != 0 )
invoke lstrcmp, input, esi
add esi, 5
inc ebx
.break .if ebx > 16  || byte ptr [esi] == 0
.endw
mov eax, ebx

ret
RetrieveHexValueFromTable endp

hextables:
db '0000',0 ; 0
db '0001',0 ; 1
db '0010',0 ; 2
db '0011',0 ; 3
db '0100',0 ; 4
db '0101',0 ; 5
db '0110',0 ; 6
db '0111',0 ; 7
db '1000',0 ; 8
db '1001',0 ; 9
db '1010',0 ; 0A
db '1011',0 ; 0B
db '1100',0 ; 0C
db '1101',0 ; 0D
db '1110',0 ; 0E
db '1111',0 ; 0F
db 00,00,00,00,00 ; null terminating block

end start

Feel free to optimize or develop..
Title: Re: binary to ascii
Post by: dedndave on January 03, 2013, 07:27:32 PM
a look-up table does not seem to be a logical solution to this type of problem
this is more of a "parsing a stream of bytes" problem
once you have the 8 bits in a single byte, the "look-up" part is done for you by way of the definition of the ASCII table
all you have to do is plop the byte down and go to the next one   :P

a little understanding of how look-up tables are beneficial might help
let's say we want to convert a binary dword into an ascii decimal string
rather than dividing by 10 and converting each remainder to an ascii character,
you might divide by 10000 and use the remainder as an index into a look-up table
that index would then yield 4 ascii characters that you can place into the resulting string
the result is very fast, although, the look-up table is 40,000 bytes in size
that would be ok if you had millions of numbers to convert
as it happens, Drizz wrote a little snippet that converts a binary value of 0-9999 to 4 ascii chars in about 18 cycles

that type of conversion just isn't practical for what you want to do
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 03, 2013, 07:59:13 PM
@ Dubby thanks I will look at it and see what I can learn about LUT's

@ dedndave 
Even though this is solved and we have a routine to convert binary to ascii text a few post back
I never did any thing with LUT , I wanted some experience with it as practice
I agree that Donkeys method is fast and efficient!
This was just perfect opportunity for me to get a little experience with it
It should have been straight forward , I will mess with it some more...
I don't know what I am doing wrong
Title: Re: binary to ascii
Post by: jj2007 on January 03, 2013, 08:05:19 PM
Quote from: hfheatherfox07 on January 03, 2013, 01:57:29 PMBut I am Getting an empty result

Get some sleep ;-)
With a few changes, it shows something, see below. But you should really, really use OllyDbg - it is much easier than trial & error.

        invoke MessageBox,NULL, addr buffer, addr szCapt,MB_OK
...
        mov esi, pszString    ; point to source
        mov edi, pBuffer    ; point to destination
...
        mov [edi], dx    ; write the output
        add edi, 2    ; update destination pointer
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 03, 2013, 09:45:31 PM
Yes I should go to sleep it is 5:40 Am

I am a little embarrassed :redface:
By my brain fart .... I used a template of an ASCII to hex string LUT
Looking back at Donkey's example he uses
Mov ecx, 7 since each ASCII character is represented by 7 '0' and '1'
And I was using movzx eax,byte ptr [esi]   ;get next byte
No wonder it did not work lol

Wops  :icon_redface:
I will take a fresh look at later when I wake up lol
Title: Re: binary to ascii
Post by: dedndave on January 04, 2013, 03:09:26 AM
ok - here is my little routine
it may not be as fast as Edgar's,
but, the destination buffer size is tested and not exceeded
and, it uses all non-binary chars as delimiters
or, if there are no delimiters, it will use 8 binary digits for each byte
if it gets to the end and there aren't 8, it assumes them to be low-order bits
if the result of a byte is 0, it makes it a space
it only terminates the output string when the input string has been fully converted
or if there would be a buffer over-run
it returns the output string length in EAX
it will handle a messy input string like this one
szTest      db ' 1001000 01100101 1101100 01101100 1101111 0100000 01001000011001010110000101110100011010000110010101110010',0

as an added feature, i used LODSB and STOSB so that Hutch won't like me, either  :lol:
;***********************************************************************************************

Abin2Achr PROC USES EBX ESI EDI lpSrc:LPSTR,lpDest:LPSTR,dwDestSize:DWORD

        mov     ebx,dwDestSize  ;size of destination buffer
        xor     eax,eax
        mov     edi,lpDest      ;pointer to destination buffer
        or      ebx,ebx
        mov     ecx,eax
        mov     esi,lpSrc       ;pointer to source string
        jz      Ab2Ac7

        add     ebx,edi
        dec     ebx
        jmp short Ab2Ac3

Ab2Ac0: xor     al,30h
        shl     edx,1
        cmp     al,1
        jbe     Ab2Ac5

        cmp     cl,8
        jz      Ab2Ac3

        shr     edx,1

Ab2Ac1: or      dl,dl
        jnz     Ab2Ac2

        mov     dl,20h

Ab2Ac2: mov     al,dl
        stosb

Ab2Ac3: cmp     edi,ebx
        mov     al,ch
        jz      Ab2Ac6

        mov     cl,8
        mov     dl,ch

Ab2Ac4: lodsb
        or      al,al
        jz      Ab2Ac6

        xor     al,30h
        cmp     al,1
        ja      Ab2Ac4

Ab2Ac5: sbb     dl,-1
        dec     ecx
        jz      Ab2Ac1

        lodsb
        or      al,al
        jnz     Ab2Ac0

        cmp     cl,8
        jz      Ab2Ac6

        cmp     edi,ebx
        jz      Ab2Ac6

        or      dl,dl
        jz      Ab2Ac6

        mov     al,dl
        stosb
        mov     al,ch

Ab2Ac6: mov     edx,edi
        stosb
        xchg    eax,edx
        sub     eax,lpDest      ;return string length

Ab2Ac7: ret

Abin2Achr ENDP

;***********************************************************************************************
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 04, 2013, 08:18:59 PM
 :icon_redface:

Hello , I am still having some difficulty with the LUT
My plan is too look up the segment of 8 ascii Binary characters that represent an ascii charter in the LUT
Copy to buffer , when done than print buffer
Any ideas I am stuck , and just want to have an LUT version working as well

Thank you

.486p
.model flat,stdcall
option casemap:none

include \masm32\include\windows.inc
include \masm32\include\masm32.inc
include \masm32\include\kernel32.inc
include \masm32\include\user32.inc

includelib \masm32\lib\masm32.lib
includelib \masm32\lib\kernel32.lib
includelib \masm32\lib\user32.lib

Bin2ASCII proto :DWORD,:DWORD,:DWORD

.data
szCapt   db "Binary To ASCII", 0
szBinaryString  db "010000010100001001000011" ; ABC
align 16 ;make sure the lookup table is aligned in memory

Binary_table \
db  00000000b,00000001b,00000010b,00000011b,00000100b,00000101b,00000110b,00000111b
db  00001000b,00001001b,00001010b,00001011b,00001100b,00001101b,00001110b,00001111b
db  00010000b,00010001b,00010010b,00010011b,00010100b,00010101b,00010110b,00010111b
db  00011000b,00011001b,00011010b,00011011b,00011100b,00011101b,00011110b,00011111b
db  00100000b,00100001b,00100010b,00100011b,00100100b,00100101b,00100110b,00100111b
db  00101000b,00101001b,00101010b,00101011b,00101100b,00101101b,00101110b,00101111b
db  00110000b,00110001b,00110010b,00110011b,00110100b,00110101b,00110110b,00110111b
db  00111000b,00111001b,00111010b,00111011b,00111100b,00111101b,00111110b,00111111b
db  01000000b,01000001b,01000010b,01000011b,01000100b,01000101b,01000110b,01000111b
db  01001000b,01001001b,01001010b,01001011b,01001100b,01001101b,01001110b,01001111b
db  01010000b,01010001b,01010010b,01010011b,01010100b,01010101b,01010110b,01010111b
db  01011000b,01011001b,01011010b,01011011b,01011100b,01011101b,01011110b,01011111b
db  01100000b,01100001b,01100010b,01100011b,01100100b,01100101b,01100110b,01100111b
db  01101000b,01101001b,01101010b,01101011b,01101100b,01101101b,01101110b,01101111b
db  01110000b,01110001b,01110010b,01110011b,01110100b,01110101b,01110110b,01110111b
db  01111000b,01111001b,01111010b,01111011b,01111100b,01111101b,01111110b,01111111b
db  10000000b,10000001b,10000010b,10000011b,10000100b,10000101b,10000110b,10000111b
db  10001000b,10001001b,10001010b,10001011b,10001100b,10001101b,10001110b,10001111b 
db  10010000b,10010001b,10010010b,10010011b,10010100b,10010101b,10010110b,10010111b
db  10011000b,10011001b,10011010b,10011011b,10011100b,10011101b,10011110b,10011111b
db  10100000b,10100001b,10100010b,10100011b,10100100b,10100101b,10100110b,10100111b
db  10101000b,10101001b,10101010b,10101011b,10101100b,10101101b,10101110b,10101111b
db  10110000b,10110001b,10110010b,10110011b,10110100b,10110101b,10110110b,10110111b
db  10111000b,10111001b,10111010b,10111011b,10111100b,10111101b,10111110b,10111111b
db  11000000b,11000001b,11000010b,11000011b,11000100b,11000101b,11000110b,11000111b
db  11001000b,11001001b,11001010b,11001011b,11001100b,11001101b,11001110b,11001111b
db  11010000b,11010001b,11010010b,11010011b,11010100b,11010101b,11010110b,11010111b
db  11011000b,11011001b,11011010b,11011011b,11011100b,11011101b,11011110b,11011111b
db  11100000b,11100001b,11100010b,11100011b,11100100b,11100101b,11100110b,11100111b
db  11101000b,11101001b,11101010b,11101011b,11101100b,11101101b,11101110b,11101111b
db  11110000b,11110001b,11110010b,11110011b,11110100b,11110101b,11110110b,11110111b
db  11111000b,11111001b,11111010b,11111011b,11111100b,11111101b,11111110b,11111111b
.data?

buffer   db 4096 dup(?) ; buffer

.code

start:

invoke Bin2ASCII,addr szBinaryString,addr buffer,sizeof szBinaryString
invoke MessageBox,NULL, addr buffer,addr szCapt,MB_OK
Invoke ExitProcess,0

Bin2ASCII proc  sourcedata:DWORD, stringbuffer:DWORD, sourcelength:DWORD


    push ebx ; register
    push esi ; register
    push edi ; register
mov esi, [sourcedata]    ;point to source
mov edi, [stringbuffer]  ;point to destination
mov ecx, [sourcelength]   ;counter into source file


mov BYTE PTR [edi], 0           ; set destination buffer to zero length

xor ebx, ebx  ; clear ebx

; scan table
align 16      ;make sure the next instruction starts on a 16 byte boundary.
scan:

movzx eax, BYTE PTR [esi]
    add esi, 1
    cmp BYTE PTR [Binary_table+eax],8    ; delimiting character
    je scan
copystring:
; copy table
mov [edi],dx               ;write the output
add edi,3                  ;update destination pointer
     
inc esi                    ;update pointer
dec ecx                    ;update count
jnz copystring
    xor eax, eax                   
ret

    pop edi  ;restore registers
    pop esi  ;restore registers
    pop ebx  ;restore registers




Bin2ASCII endp
end start
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 05, 2013, 05:40:09 PM
I really Need help with the LUT format !!!!

As you can see I read the3 LUT with ebx

.486p
.model flat,stdcall
option casemap:none

include \masm32\include\windows.inc
include \masm32\include\masm32.inc
include \masm32\include\kernel32.inc
include \masm32\include\user32.inc

includelib \masm32\lib\masm32.lib
includelib \masm32\lib\kernel32.lib
includelib \masm32\lib\user32.lib

Bin2ASCII proto :DWORD,:DWORD

.data
szCapt   db "Binary To ASCII", 0
szBinaryString  db "010000010100001001000011",0 ; ABC
.data?
buffer   db 4096 dup(?) ; buffer

.code

start:

invoke Bin2ASCII,addr szBinaryString,addr buffer
invoke MessageBox,NULL, ebx,addr szCapt,MB_OK
Invoke ExitProcess,0
Bin2ASCII proc   pszString:DWORD,pBuffer:DWORD


pushad                 ;save all cpu registers



lea ebx,Binary_table      ;get the address of the lookup table


ALIGN 16      ;make sure the next instruction starts on a 16 byte boundary.


mov edx,[8*eax+ebx]        ;look up Binary

; at this Point the LUT values are ebx
xor eax, eax
ret
popad                      ;restore all cpu registers

ALIGN 16  ;make sure the lookup table is aligned in memory
Binary_table:
;01000001b = A 01000010 = B 01000011 = C   
db  01000001b,01000010b,01000011b,"  30","  40","  50","  60","  70"
db "  80","  90","  A0","  B0","  C0","  D0","  E0","  F0"
db "  01","  11","  21","  31","  41","  51","  61","  71"
db "  81","  91","  A1","  B1","  C1","  D1","  E1","  F1"
db "  02","  12","  22","  32","  42","  52","  62","  72"
db "  82","  92","  A2","  B2","  C2","  D2","  E2","  F2"
db "  03","  13","  23","  33","  43","  53","  63","  73"
db "  83","  93","  A3","  B3","  C3","  D3","  E3","  F3"
db "  04","  14","  24","  34","  44","  54","  64","  74"
db "  84","  94","  A4","  B4","  C4","  D4","  E4","  F4"
db "  05","  15","  25","  35","  45","  55","  65","  75"
db "  85","  95","  A5","  B5","  C5","  D5","  E5","  F5"
db "  06","  16","  26","  36","  46","  56","  66","  76"
db "  86","  96","  A6","  B6","  C6","  D6","  E6","  F6"
db "  07","  17","  27","  37","  47","  57","  67","  77"
db "  87","  97","  A7","  B7","  C7","  D7","  E7","  F7"
db "  08","  18","  28","  38","  48","  58","  68","  78"
db "  88","  98","  A8","  B8","  C8","  D8","  E8","  F8"
db "  09","  19","  29","  39","  49","  59","  69","  79"
db "  89","  99","  A9","  B9","  C9","  D9","  E9","  F9"
db "  0A","  1A","  2A","  3A","  4A","  5A","  6A","  7A"
db "  8A","  9A","  AA","  BA","  CA","  DA","  EA","  FA"
db "  0B","  1B","  2B","  3B","  4B","  5B","  6B","  7B"
db "  8B","  9B","  AB","  BB","  CB","  DB","  EB","  FB"
db "  0C","  1C","  2C","  3C","  4C","  5C","  6C","  7C"
db "  8C","  9C","  AC","  BC","  CC","  DC","  EC","  FC"
db "  0D","  1D","  2D","  3D","  4D","  5D","  6D","  7D"
db "  8D","  9D","  AD","  BD","  CD","  DD","  ED","  FD"
db "  0E","  1E","  2E","  3E","  4E","  5E","  6E","  7E"
db "  8E","  9E","  AE","  BE","  CE","  DE","  EE","  FE"
db "  0F","  1F","  2F","  3F","  4F","  5F","  6F","  7F"
db "  8F","  9F","  AF","  BF","  CF","  DF","  EF","  FF"

Bin2ASCII endp
end start


Why Is it when I add the full table it won't read it any more????
db  00000000b,00000001b,00000010b,00000011b,00000100b,00000101b,00000110b,00000111b
db  00001000b,00001001b,00001010b,00001011b,00001100b,00001101b,00001110b,00001111b
db  00010000b,00010001b,00010010b,00010011b,00010100b,00010101b,00010110b,00010111b
db  00011000b,00011001b,00011010b,00011011b,00011100b,00011101b,00011110b,00011111b
db  00100000b,00100001b,00100010b,00100011b,00100100b,00100101b,00100110b,00100111b
db  00101000b,00101001b,00101010b,00101011b,00101100b,00101101b,00101110b,00101111b
db  00110000b,00110001b,00110010b,00110011b,00110100b,00110101b,00110110b,00110111b
db  00111000b,00111001b,00111010b,00111011b,00111100b,00111101b,00111110b,00111111b
db  01000000b,01000001b,01000010b,01000011b,01000100b,01000101b,01000110b,01000111b
db  01001000b,01001001b,01001010b,01001011b,01001100b,01001101b,01001110b,01001111b
db  01010000b,01010001b,01010010b,01010011b,01010100b,01010101b,01010110b,01010111b
db  01011000b,01011001b,01011010b,01011011b,01011100b,01011101b,01011110b,01011111b
db  01100000b,01100001b,01100010b,01100011b,01100100b,01100101b,01100110b,01100111b
db  01101000b,01101001b,01101010b,01101011b,01101100b,01101101b,01101110b,01101111b
db  01110000b,01110001b,01110010b,01110011b,01110100b,01110101b,01110110b,01110111b
db  01111000b,01111001b,01111010b,01111011b,01111100b,01111101b,01111110b,01111111b
db  10000000b,10000001b,10000010b,10000011b,10000100b,10000101b,10000110b,10000111b
db  10001000b,10001001b,10001010b,10001011b,10001100b,10001101b,10001110b,10001111b 
db  10010000b,10010001b,10010010b,10010011b,10010100b,10010101b,10010110b,10010111b
db  10011000b,10011001b,10011010b,10011011b,10011100b,10011101b,10011110b,10011111b
db  10100000b,10100001b,10100010b,10100011b,10100100b,10100101b,10100110b,10100111b
db  10101000b,10101001b,10101010b,10101011b,10101100b,10101101b,10101110b,10101111b
db  10110000b,10110001b,10110010b,10110011b,10110100b,10110101b,10110110b,10110111b
db  10111000b,10111001b,10111010b,10111011b,10111100b,10111101b,10111110b,10111111b
db  11000000b,11000001b,11000010b,11000011b,11000100b,11000101b,11000110b,11000111b
db  11001000b,11001001b,11001010b,11001011b,11001100b,11001101b,11001110b,11001111b
db  11010000b,11010001b,11010010b,11010011b,11010100b,11010101b,11010110b,11010111b
db  11011000b,11011001b,11011010b,11011011b,11011100b,11011101b,11011110b,11011111b
db  11100000b,11100001b,11100010b,11100011b,11100100b,11100101b,11100110b,11100111b
db  11101000b,11101001b,11101010b,11101011b,11101100b,11101101b,11101110b,11101111b
db  11110000b,11110001b,11110010b,11110011b,11110100b,11110101b,11110110b,11110111b
db  11111000b,11111001b,11111010b,11111011b,11111100b,11111101b,11111110b,11111111b

:( :( :(

If anybody knows I would appreciate it



Title: Re: binary to ascii
Post by: MichaelW on January 05, 2013, 06:44:40 PM
I don't understand the purpose of the second LUT. What would be the point of looking up a value in a table where the indexed value is equal to the index?

Title: Re: binary to ascii
Post by: hfheatherfox07 on January 05, 2013, 06:56:14 PM
Quote from: MichaelW on January 05, 2013, 06:44:40 PM
I don't understand the purpose of the second LUT. What would be the point of looking up a value in a table where the indexed value is equal to the index?


I feel a llittle dumb .... :redface:
I have no idea what do you means?
The first LUT is a Hex table LUT that I modified to include
3 binary values only ....A B C
If you run that little snippet above it you will see that it successfully shows  ABC than all the hex
Does that make senesce?
I do not know why I can't get the second proper LUT
to work the same ? It should ? 
Title: Re: binary to ascii
Post by: MichaelW on January 05, 2013, 09:08:15 PM
Quote from: hfheatherfox07 on January 05, 2013, 06:56:14 PM
I feel a llittle dumb .... :redface:

Everyone makes mistakes. The key is to catch them before you post :biggrin:

Quote
I have no idea what do you means?

For an example of a working LUT look in masm32\m32lib\bintbl.asm. To use that table you start with a byte value (a number between 0 and 255 inclusive) and use the value as an index into the table, and read the 8-byte binary string representation of the number. See b2b_ex.asm in the same directory for an example of using the table.

In the linked example, the translation is between the string on the left and a larger string of binary digits on the right, were each 8-digit group represents the character code of a character from the string on the left. So the translation, either way, starts and ends with a string.

So it looks like an easy way to translate from text to binary would be to loop through the characters in the text passing each character code to byt2bin_ex along with an appropriate buffer address. Your buffer will need to be large enough to accommodate 8 bytes per character, plus a terminating null. And after each character you will need to add 8 to the buffer address.

And to translate from binary to text you could loop through the binary 8-digits at a time, passing the address of each 8-digit group to bin2byte_ex, and then used the returned values, each a character code, to construct your text string.

Sorry, I don't have time to actually test any of this.

Or you could use your own LUTs and procedures, to do essentially the same thing.
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 05, 2013, 09:21:03 PM
I was trying to use My own LUT ...that is what I am having a problem with  :(
Donkey wrote a beautiful proc to translate this and it works ,I just want some experience with LUT
I still did not catch why that table that I am trying to use wont work 
Title: Re: binary to ascii
Post by: dedndave on January 05, 2013, 09:27:05 PM
maybe you missed this post...

http://masm32.com/board/index.php?topic=1122.msg11779#msg11779 (http://masm32.com/board/index.php?topic=1122.msg11779#msg11779)
Title: Re: binary to ascii
Post by: Donkey on January 08, 2013, 08:11:38 AM
I think the only place I've ever used a LUT was when converting case, though I doubt its as quick as most other ways of doing it I wanted to try xlatb and have just kept using it ever since...

align 16
lcase:
db   0,  1,  2,  3,  4,  5,  6,  7,  8,  9, 10, 11, 12, 13, 14, 15
db  16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31
db  32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47
db  48, 49, 50, 51, 52, 53, 54, 55, 56, 57, 58, 59, 60, 61, 62, 63
db  64, 97, 98, 99,100,101,102,103,104,105,106,107,108,109,110,111
db 112,113,114,115,116,117,118,119,120,121,122, 91, 92, 93, 94, 95
db  96, 97, 98, 99,100,101,102,103,104,105,106,107,108,109,110,111
db 112,113,114,115,116,117,118,119,120,121,122,123,124,125,126,127
db 128,129,130,131,132,133,134,135,136,137,138,139,140,141,142,143
db 144,145,146,147,148,149,150,151,152,153,154,155,156,156,158,159
db 160,161,162,163,164,165,166,167,168,169,170,171,172,173,173,175
db 176,177,178,179,180,181,182,183,184,185,186,187,188,189,190,191
db 192,193,194,195,196,197,198,199,200,201,202,203,204,205,206,207
db 208,209,210,211,212,213,214,215,216,217,218,219,220,221,222,223
db 224,225,226,227,228,229,230,231,232,233,234,235,236,237,238,239
db 240,241,242,243,244,245,246,247,248,249,250,251,252,253,254,255

ucase:
db   0,  1,  2,  3,  4,  5,  6,  7,  8,  9, 10, 11, 12, 13, 14, 15
db  16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31
db  32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47
db  48, 49, 50, 51, 52, 53, 54, 55, 56, 57, 58, 59, 60, 61, 62, 63
db  64, 65, 66, 67, 68, 69, 70, 71, 72, 73, 74, 75, 76, 77, 78, 79
db  80, 81, 82, 83, 84, 85, 86, 87, 88, 89, 90, 91, 92, 93, 94, 95
db  96, 65, 66, 67, 68, 69, 70, 71, 72, 73, 74, 75, 76, 77, 78, 79
db  80, 81, 82, 83, 84, 85, 86, 87, 88, 89, 90,123,124,125,126,127
db 128,129,130,131,132,133,134,135,136,137,138,139,140,141,142,143
db 144,145,146,147,148,149,150,151,152,153,154,155,156,156,158,159
db 160,161,162,163,164,165,166,167,168,169,170,171,172,173,173,175
db 176,177,178,179,180,181,182,183,184,185,186,187,188,189,190,191
db 192,193,194,195,196,197,198,199,200,201,202,203,204,205,206,207
db 208,209,210,211,212,213,214,215,216,217,218,219,220,221,222,223
db 224,225,226,227,228,229,230,231,232,233,234,235,236,237,238,239
db 240,241,242,243,244,245,246,247,248,249,250,251,252,253,254,255

lszCase FRAME pString,fCase
uses ebx,esi,edi

mov ebx,offset lcase
cmp D[fCase],1
jne >
mov ebx,offset ucase
:

mov edi,[pString]
mov esi,[pString]
xor ecx,ecx
:
mov al,[esi+ecx]
xlatb
mov [edi+ecx],al
inc ecx
or al,al
jnz <
:

mov eax,edi
RET
ENDF
Title: Re: binary to ascii
Post by: dedndave on January 08, 2013, 10:41:34 AM
don't let Hutch see that XLAT instruction   :lol:
we can't afford to have Edgar banished
Title: Re: binary to ascii
Post by: Donkey on January 08, 2013, 11:02:03 AM
Quote from: dedndave on January 08, 2013, 10:41:34 AM
we can't afford to have Edgar banished

LOL, I think he might cut me some slack this one time...
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 08, 2013, 06:46:59 PM
Quote from: Donkey on January 08, 2013, 08:11:38 AM
I think the only place I've ever used a LUT was when converting case, though I doubt its as quick as most other ways of doing it I wanted to try xlatb and have just kept using it ever since...



@Donkey
My Problem is the fourth post up from the bottom on the previous page...when I try to add the full LUT table it won't work
The solution that you have previously posted was elegant and fast and that is what I will be using , Thank you again  :t
I just wanted to make an LUT example , Since I never made any thing with an LUT before.
Title: Re: binary to ascii
Post by: hfheatherfox07 on January 08, 2013, 08:08:51 PM
@Donkey  is this what you had in mind with your case convert ?
I tried Converting it to masm ... It converts upper case to lower case....

.486p
.model flat,stdcall
option casemap:none

include \masm32\include\windows.inc
include \masm32\include\masm32.inc
include \masm32\include\kernel32.inc
include \masm32\include\user32.inc

includelib \masm32\lib\masm32.lib
includelib \masm32\lib\kernel32.lib
includelib \masm32\lib\user32.lib

lszCase proto :DWORD,:DWORD

.data
align 16
_lcase\
db   0,  1,  2,  3,  4,  5,  6,  7,  8,  9, 10, 11, 12, 13, 14, 15
db  16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31
db  32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47
db  48, 49, 50, 51, 52, 53, 54, 55, 56, 57, 58, 59, 60, 61, 62, 63
db  64, 97, 98, 99,100,101,102,103,104,105,106,107,108,109,110,111
db 112,113,114,115,116,117,118,119,120,121,122, 91, 92, 93, 94, 95
db  96, 97, 98, 99,100,101,102,103,104,105,106,107,108,109,110,111
db 112,113,114,115,116,117,118,119,120,121,122,123,124,125,126,127
db 128,129,130,131,132,133,134,135,136,137,138,139,140,141,142,143
db 144,145,146,147,148,149,150,151,152,153,154,155,156,156,158,159
db 160,161,162,163,164,165,166,167,168,169,170,171,172,173,173,175
db 176,177,178,179,180,181,182,183,184,185,186,187,188,189,190,191
db 192,193,194,195,196,197,198,199,200,201,202,203,204,205,206,207
db 208,209,210,211,212,213,214,215,216,217,218,219,220,221,222,223
db 224,225,226,227,228,229,230,231,232,233,234,235,236,237,238,239
db 240,241,242,243,244,245,246,247,248,249,250,251,252,253,254,255

_ucase\
db   0,  1,  2,  3,  4,  5,  6,  7,  8,  9, 10, 11, 12, 13, 14, 15
db  16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31
db  32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47
db  48, 49, 50, 51, 52, 53, 54, 55, 56, 57, 58, 59, 60, 61, 62, 63
db  64, 65, 66, 67, 68, 69, 70, 71, 72, 73, 74, 75, 76, 77, 78, 79
db  80, 81, 82, 83, 84, 85, 86, 87, 88, 89, 90, 91, 92, 93, 94, 95
db  96, 65, 66, 67, 68, 69, 70, 71, 72, 73, 74, 75, 76, 77, 78, 79
db  80, 81, 82, 83, 84, 85, 86, 87, 88, 89, 90,123,124,125,126,127
db 128,129,130,131,132,133,134,135,136,137,138,139,140,141,142,143
db 144,145,146,147,148,149,150,151,152,153,154,155,156,156,158,159
db 160,161,162,163,164,165,166,167,168,169,170,171,172,173,173,175
db 176,177,178,179,180,181,182,183,184,185,186,187,188,189,190,191
db 192,193,194,195,196,197,198,199,200,201,202,203,204,205,206,207
db 208,209,210,211,212,213,214,215,216,217,218,219,220,221,222,223
db 224,225,226,227,228,229,230,231,232,233,234,235,236,237,238,239
db 240,241,242,243,244,245,246,247,248,249,250,251,252,253,254,255

szCapt   db "Donkey's Case Convert", 0
szString  db "I AM ALL LOWER CASE LETTERS"
.data?

buffer   db 4096 dup(?) ; buffer
D dd ?
.code

start:

invoke lszCase,addr szString,addr buffer
invoke MessageBox,NULL,eax,addr szCapt,MB_OK
Invoke ExitProcess,0
lszCase proc uses ebx esi edi pString:DWORD,fCase:DWORD


mov ebx,offset _lcase
cmp D [fCase],1
jne something
mov ebx,offset _ucase
something:

mov edi,[pString]
mov esi,[pString]
xor ecx,ecx
something2:
mov al,[esi+ecx]
xlatb
mov [edi+ecx],al
inc ecx
or al,al
jnz something2
Done:

mov eax,edi
ret
lszCase endp
end start