flat assembler
Message board for the users of flat assembler.

Index > Main > expressions evaluator

Author
Thread Post new topic Reply to topic
idle



Joined: 06 Jan 2011
Posts: 440
Location: Ukraine
idle 11 Jun 2011, 14:19
hello
common release was written after bug detection in a cool debugger
i was also wondering to adorn that product
hence there is no cool interface(scarce test.asm only), dumpers(that was stupid idea at all), float methods(qwords should be tested 1st)
download link: http://fasmme.googlecode.com/files/calc.zip
refs to: http://board.flatassembler.net/topic.php?p=130409#130409

english copy-past:
Code:
enu: expression evaluator written in fasm(www.FlatAssembler.net), polished in ollydbg(www.OllyDbg.de)
     -----------------------------------------------------------
     stdcall params are:
       type - q or Q denote qword(integer) mode to be used, tbyte(float) else
              just entered, calc calls ascii_lower(see respective file) and rewrites type value
              in qword mode numbers occupy 8 bytes, 10 bytes else
              see get_number file for supported notations
              tbyte mode requires fpu present to execute FINIT instruction first
              if no floater detected, error returned(flags.cf=1)

       text - expression in human readable form
              terminate with byte 0: text db '1+1',0

       temp - converted expression will lie here
              must be (12 times)+1 longer text:
                text db '1+1',0
                  .:
                temp rb (text.-text)*12+1
                  .:
     -----------------------------------------------------------
     next three stdcall params extend calc's functionality but may be all zero
     if access to old regs or calc params needed:
             calc params
             ret point
             pusha
     [ebp] = pushf or 1(flags.cf=1)

       pGetChr - used when searching for a keyword
                 if 0, calc puts address of ascii_lower there to be a bit ignorant :)
                 use RET to follow char case
                 when pGetChr called, calc is busy much so there are no free regs
                 now look at ascii_lower - nothing odd but AL register changing
                 pGetChr should do same, returning AL lower or upper
                 the simplest sample:
                   pGetChr:push    ebx
                           mov     ebx,some_table
                           xlatb
                           pop     ebx
                           ret     0

       pGetKey - ignored if 0, else calc executes CLD and CALL ECX
                 there is no need to CLD or restore regs(but mentioned) on exit
                 1st calc tries to match keyword
                 being unsatisfied within internal structures, calc calls pGetKey
                 the simplest sample:
                   pGetKey:mov     al,[esi]
                           cmp     al,'A'            ;etc data
                           je      .ok
                           cmp     al,'a'            ;etc data
                           je      .ok
                           stc                       ;makes calc search for numbers now
                           ret     0                 ;restore esi,edi
                     .ok:  inc     esi               ;add esi,sizeof(etc data)
                           mov     al,2              ;say calc this is element-number
                           stosb
                           mov     eax,'Cool'        ;qword.lo
                           stosd
                           mov     eax,'Fool'        ;qword.hi
                           stosd
                           add     edi,12-9          ;element size = 12 bytes  <- flags.cf is off, this informs calc not to search for numbers
                           ret     0

       pGetMem - ignored if 0, else calc ececutes CLD and CALL [calc.pGetMem]
                 there is no need to CLD or restore regs(but mentioned) on exit
                 after calc calculated [expression in such braces], pGetMem called and expected to bring a value from [a value]
                 the simplest sample:
                   pGetMem:inc     edi               ;pose at number body
                           mov     esi,[edi]         ;get qword.lo
                           invoke  IsBadReadPtr,esi,4;use some os function to ensure
                           test    eax,eax
                           jz      .ok
                           stc                       ;report error
                           ret     0
                     .ok:  lodsd                     ;load at esi
                           stosd                     ;store at edi
                           sub     eax,eax           ;etc
                           stosd
                           add     edi,12-9          ;pose behind result
                           ret     0                 ;flags.cf cleared by previous instro
     -----------------------------------------------------------
     on exit:
       flags.cf  - error state
       [temp+12] - element-result or byte 0
       fpu       - ?
     -----------------------------------------------------------
     there are two stages of the job: recognition and execution
     recognition implies matching keywords, skipping 9(tab),10(lf),13(cr),32(space), storing (<[]>) as is, encoding numbers

     () or [] form blocks, executed one by one
     calc does not distinguish () and [] if not a call to pGetMem required
     queuing for ((())) = (3rd(2nd(1st)))
     queuing for (()()) = (3rd(1st)(2nd))
     empty blocks will be unbraced:
       (()())                =
       (number1 numer2)      = number1 numer2
       (operator1 operator2) = operator1 operator2

     <> denote execution direction
     < is right to left and chosen default
     > is left to right
     use as many <> as needed
     <> have their strength within single block and discarded after its calculation
     < 1 shl 2 shl 3 = 1 shl (2 shl 3) = 1 shl 16 = 65'536
     > 1 shl 2 shl 3 = (1 shl 2) shl 3 = 4 shl  3 =     32

     pGetChr & pGetKey act during this period
     -----------------------------------------------------------
     execution starts at calc.recognized: point and temp looks:
       ;header
       dd 0,0,0
       ;methods
       db 1
       dd method
       align 12
       ;numbers
       db 2
       dq|dt number
       align 12
       ;(<>)
       db 2 dup as is
       align 12
       ;[
       db (,[
       align 12
       ;]
       db ),]
       align 12
       ;footer
       db 0

     CLD precedes any method call
     there is no need to CLD or restore regs(but mentioned) on exit
     use method macro(see behind calc's body) to create those
     method macro params are:
       pointer - or method
                 is an entry point keyword stays for
                 next macro params define data before this label
       type    - use q or Q to inform calc this is qword method
                 type used on recognition stage and calc filters methods due active mode
                 so qwords disallowed in tbyte mode and vv
       prio    - method's priority
                 the bigger the earlier call
                 it's recommended to use -1=255=$ff if putting constants is the deal
                 prioritization used on execution
       aliases - used during key matching
                 those are possible variations of same address - pointer
     on call regs are:
       eax - number of left params
       ebx - number of right params
       ecx - element-method pointer in temp
       edi - left-most element-number pointer or =ECX if EAX=0
       esi - right-most element-number pointer+12 or =ECX+12 if EBX=0
     on exit:
       EDI must point behind 12 bytes result
       execute STC calc to return error

     pGetMem run here
    
Post 11 Jun 2011, 14:19
View user's profile Send private message Reply with quote
idle



Joined: 06 Jan 2011
Posts: 440
Location: Ukraine
idle 12 Jun 2011, 02:28
Post 12 Jun 2011, 02:28
View user's profile Send private message Reply with quote
idle



Joined: 06 Jan 2011
Posts: 440
Location: Ukraine
idle 01 Jul 2011, 09:09
hello

calc uses cpuid to detect fpu-on-chip and that is wrong:
-specific i486's and over required
-external co-processors ignored ?
-emulators ignored ?

as mov eax,cr0 may be unavailable, smsw with consecutive and & test should be used
intel and amd say smsw eax does not modify high part but it does
actually i do not care about eax.hi but why?
Post 01 Jul 2011, 09:09
View user's profile Send private message Reply with quote
sinsi



Joined: 10 Aug 2007
Posts: 789
Location: Adelaide
sinsi 01 Jul 2011, 09:22
Intel say that if using SMSW with a 32-bit register the upper 16 bits are 'undefined', at the moment it seems that they are the bits from CR0.
Maybe not in the future...
Post 01 Jul 2011, 09:22
View user's profile Send private message Reply with quote
idle



Joined: 06 Jan 2011
Posts: 440
Location: Ukraine
idle 01 Jul 2011, 09:47
is that ok?
Code:
        ;mov     eax,1
        ;cpuid
        ;test    dl,1
        ;jz      .exit                  ;no floats support
        hlt
        smsw                            ;mov eax,cr0
        and     al,110b                 ;filter Emulation+MathPresent
        jz      .exit                   ;neither nor Sad
        finit
    
Post 01 Jul 2011, 09:47
View user's profile Send private message Reply with quote
idle



Joined: 06 Jan 2011
Posts: 440
Location: Ukraine
idle 03 Jul 2011, 17:46
next code shows how to add bt? operators:
Code:
;prefer amd's to intel's manual about bit test instructions
;if a person reads 1 book that is a problem...

;v bt  v  <- this gets flags.cf
;v btc v  <- these modify value
;v btr v
;v bts v
macro _[p1]{
method i386.#p1, q, 0, `p1
        cmp     ebx,1
        jne     .nok          ;right params must be 1
        cmp     eax,ebx
        jne     .nok          ;left params too
        inc     edi
        mov     ecx,[edi+12*2];skip left param & this method, load right param
        and     ecx,63
        p1      [edi],ecx
  if p1 eq bt
        setc    cl
        mov     [edi],ecx     ;0 or 1
        mov     cl,0
        mov     [edi+4],ecx   ;0
  end if
        add     edi,12-1      ;pose behind result
        ret     0             ;flags.cf cleared by ADD-instruction
  .nok: stc
        ret     0
}
_ bt,btc,btr,bts
purge _
    
Post 03 Jul 2011, 17:46
View user's profile Send private message Reply with quote
idle



Joined: 06 Jan 2011
Posts: 440
Location: Ukraine
idle 23 Jul 2011, 08:20
calc.inc changes:
-smsw: i have no words
Code:
        or      byte[.type],' '
        cmp     byte[.type],'q'
        je      .type_q                ;qword mode
        smsw    eax                    ;mov eax,cr0
        and     al,110b                ;filter Emulation+MathPresent
;        jz      .exit                  ;neither nor :(
;jnz @f
;invoke MessageBoxA,0,'SMSW EAX says neither emulation nor fpu present... bOOm... try several times... does it?... is this windows bug(but win xp runs on fpu-served processors)?... is this our AMD bug... am i stupid?... who is the bug? why does SMSW write high part of EAX?... correct your manuals: you have said EAX.HI UNDEFINED both(but INC is UNDEFINED ie UNALTERED with CF flag)... i am sad, thanx :(',0,0
;@@:
    

-operators filtering is very simple now(where have i been ?)
Code:
        dec     edx                    ;we are at method type
        mov     al,[edx]
        or      al,' '
        cmp     al,byte[.type]
        jne     .find_longer_key
    

-prioritization did not work

get_number.inc changes:
-some dummies removed
-floats in binary and hex notation contained extra two bytes(12 instead 10)
-floats routine updated
Code:
.d_:                              ;read <frac> intro 1st
        bt      ecx,30            ;point met?
        jc      .d_dl_defined     ;by .point:
        mov     dl,cl             ;all part is integer
    .d_dl_defined:
        mov     [esp-4-1],dl
        call    frac
        js      .d_z              ;zero, flags=$ff-$00
        not     ecx               ;(neg ecx - 2) = (not ecx + 1 - 2) = (not ecx - 1)
        dec     ecx
        and     cx,$3fff          ;biased power of 2
        mov     [esp-4],esi       ;(at-1) $ff
        mov     esi,edx           ;esi:ebp:ebx = .fraction
    .d_mul:
        sub     byte[esp-4-1],1
        jz      .d_nz             ;flags.cf = 0
        ;esi
        mov     eax,10
        mul     esi
        mov     esi,eax
        mov     edi,edx
        ;ebp
        mov     eax,10
        mul     ebp
        mov     ebp,eax
        add     esi,edx
        adc     edi,0
        ;ebx
        mov     eax,10
        mul     ebx
        mov     ebx,eax
        add     ebp,edx
        adc     esi,0
        adc     edi,0
        ;normalize
        mov     eax,ecx
        bsr     ecx,edi
        inc     ecx
        add     eax,ecx
        shrd    ebx,ebp,cl
        shrd    ebp,esi,cl
        shrd    esi,edi,cl
        mov     ecx,eax
        jmp     .d_mul
    .d_nz:
        ;weak rounding
        test    ebx,ebx
        jns     .rounded
        add     ebp,1
        adc     esi,0
        jnc     .rounded
        rcr     esi,1
        rcr     ebp,1
        inc     ecx
    .rounded:
        ;store
        mov     edi,[esp-4]
        inc     edi
        mov     eax,ebp
        stosd
        mov     eax,esi
        stosd
        mov     eax,ecx
        stosw
        mov     al,'d'
        pop     esi
        ret     0
    .d_z:
        inc     edi
        stosd
        stosd
        stosw
        mov     al,'d'
        pop     esi
        ret     0
    


simple_dumpers.inc adds next dumping modes:
Code:
include once 'd^x.inc' ;tbyte_sdec
include once 'daa_.inc' ;hex




;src -> esi
;dest -> edi
;eax,ebx,ecx,edx,esi,edi,flags <- ?

align 4
simple_dumpers:

macro _[entry_point,description]{
forward
  dd entry_point,0
common
  dd 0
  local base
  base=simple_dumpers+4
forward
  store dword $ at base
  base=base+8
  db description,0
}
_ \
  tbyte_sdec,"tbyte_sdec",\
  tbyte_hex,"tbyte_hex",\
  \
  \
  asis.88,"asis.88: qword",\
  asis.44,"asis.44: dword",\
  asis.22,"asis.22: word",\
  asis.11,"asis.11: byte",\
  \
  bin_frac.88,"bin_frac.88: 0.qword",\
  bin_frac.44,"bin_frac.44: 0.dword",\
  bin_frac.22,"bin_frac.22: 0.word",\
  bin_frac.11,"bin_frac.11: 0.byte",\
  \
  bin.88,"bin.88: qword in qwords",\
  bin.84,"bin.84: qword in dwords",\
  bin.82,"bin.82: qword in words",\
  bin.81,"bin.81: qword in bytes",\
  bin.44,"bin.44: dword in dwords",\
  bin.42,"bin.42: dword in words",\
  bin.41,"bin.41: dword in bytes",\
  bin.22,"bin.22: word in words",\
  bin.21,"bin.21: word in bytes",\
  bin.11,"bin.11: byte in bytes",\
  \
  sdec.88,"sdec.88: signed qword",\
  sdec.44,"sdec.44: signed dword",\
  sdec.22,"sdec.22: signed word",\
  sdec.11,"sdec.11: signed byte",\
  \
  _dec.88,"_dec.88: unsigned qword",\
  _dec.44,"_dec.44: unsigned dword",\
  _dec.22,"_dec.22: unsigned word",\
  _dec.11,"_dec.11: unsigned byte",\
  \
  hex.88,"hex.88: qword in qwords",\
  hex.84,"hex.84: qword in dwords",\
  hex.82,"hex.82: qword in words",\
  hex.81,"hex.81: qword in bytes",\
  hex.44,"hex.44: dword in dwords",\
  hex.42,"hex.42: dword in words",\
  hex.41,"hex.41: dword in bytes",\
  hex.22,"hex.22: word in words",\
  hex.21,"hex.21: word in bytes",\
  hex.11,"hex.11: byte in bytes"
purge _




tbyte_sdec:
        mov     ax,[esi+8]               ;take sign bit and the power of two
        btr     eax,15                   ;drop sign bit
        jnc     .not_signed
        mov     byte[edi],"-"
        inc     edi
  .not_signed:
        cmp     dword[esi+4],0           ;check if fraction zero
        jnz     .not_zero
        cmp     dword[esi],0
        jnz     .not_zero
        mov     word[edi],"0"
        ret     0
  .undefined:
        mov     word[edi],"?"
        ret     0
  .not_zero:
        cmp     ax,$0000                 ;ok, sign does not meddle, check if unsupported
        je      .undefined
        cmp     ax,$7fff
        je      .undefined
;value at ESI equals 10^x = 10^(x.int + x.frac) = 10^x.frac * 10^x.int
;in other words we want value at ESI look dumped like this: 3.1416 * 10^0
;10^x.frac = (10^-1 .. 10^1) = (0.1 .. 10)
;x = log(10;value at esi) = log(10;2) * log(2;value at esi)
        fldlg2                           ;log(10;2)*
        fld     tbyte[esi]
        fabs
        fyl2x                            ;*log(2;value at esi) = x
        push    eax
        fist    dword[esp]               ;x.int
        fisub   dword[esp]               ;x.frac
        call    d^x
;0.abc -> a.bc
        fld1
        fcomp   st1
        fstsw   ax
        sahf
        jna     .x.frac_was_positive
        push    10
        fimul   dword[esp]
        pop     eax
        dec     dword[esp]
  .x.frac_was_positive:
;so st0 = a.bc
;now pop that one integral digit
        fstp    tbyte[edi]
        mov     cl,[edi+8]               ;cl = $ff for 1, $00 for 2, $01 for 3...
        add     cl,2                     ;so the difference is 2
        mov     eax,[edi+4]
        mov     bx,0
        shld    ebx,eax,cl               ;the pop
        add     bx,'0.'                  ;a.
        mov     esi,[edi]
        mov     [edi],bx
        add     edi,2                    ;pose behind a.
        shld    eax,esi,cl               ; = .eax:esi = some binary fraction = 0.bc
        shl     esi,cl
        mov     cx,0100'0000b shl 8 + 18 ;put dummy after a trio put, there will be 18 digits = 6 trios
        call    bin_frac
;it is time to paint x.int
        cld
        mov     ax,' *'
        stosw
        mov     eax,'10^('
        stosd
        sub     ecx,ecx
        lea     ebx,[ecx+10]
        pop     eax                      ;x.int
        test    eax,eax                  ;signed?
        jns     .x.int_positive
        neg     eax
        mov     byte[edi],"-"
        inc     edi
  .x.int_positive:
        inc     ecx
        sub     edx,edx
        div     ebx
        push    edx
        test    eax,eax
        jnz     .x.int_positive
  .swap_x.int_remainders:
        pop     eax
        add     al,"0"
        stosb
        loop    .swap_x.int_remainders
;enough :b
        mov     word[edi],")"
        ret     0




tbyte_hex:
        add     esi,9
        mov     cx,0000'0000b shl 8 + 2
        call    hex
        mov     al,"'"
        stosb
        mov     cx,1000'1000b shl 8 + 8
        jmp     hex








asis_:  cld
asis:   lodsb
        cmp     al,' '
        jae     .visible
        mov     al,'.'
      .visible:
        stosb
        loop    asis
        mov     [edi],cl
        ret     0

  .88:  mov     ecx,8
        jmp     asis_

  .44:  mov     ecx,4
        jmp     asis_

  .22:  mov     ecx,2
        jmp     asis_

  .11:  mov     ecx,1
        jmp     asis_




bin_frac__:
        sub     esi,esi
bin_frac_:
        mov     word[edi],'0.'
        add     edi,2
bin_frac:;10esi:eax = 10esi+10eax
        mov     edx,10
        mul     edx
        mov     bl,dl
        mov     dl,10
        xchg    esi,eax
        mul     edx
        add     esi,edx
        adc     bl,'0'
        mov     [edi],bl
        inc     edi
        dec     cl
        jz      .ret
        xchg    esi,eax
        add     ch,0100'0000b
        jnc     bin_frac
        mov     ch,0100'0000b
        mov     byte[edi],"'"
        inc     edi
        jmp     bin_frac
  .ret: mov     [edi],cl
        ret     0

  .88:  mov     eax,[esi+4]              ;hi
        mov     esi,[esi]                ;lo
        mov     cx,0100'0000b shl 8 + 24 ;dummy after each step #3, 24 steps
        jmp     bin_frac_

  .44:  mov     eax,[esi]
        ;sub     esi,esi
        mov     cx,0100'0000b shl 8 + 12
        jmp     bin_frac__

  .22:  mov     eax,[esi]
        shl     eax,16
        ;sub     esi,esi
        mov     cx,0100'0000b shl 8 + 6
        jmp     bin_frac__

  .11:  mov     eax,[esi]
        shl     eax,24
        ;sub     esi,esi
        mov     cx,0100'0000b shl 8 + 3
        jmp     bin_frac__




bin_:   add     esi,7
bin:    std
        lodsb
        cld
        and     eax,$ff
        mov     ebx,eax
        and     bl,$0f
        shr     al,$04
        mov     eax,[.bins+eax*4]
        stosd
        mov     eax,[.bins+ebx*4]
        stosd
        dec     cl
        jz      .ret
        shr     ch,1
        jnc     bin
        mov     al,"'"
        stosb
        jmp     bin
  .ret: mov     [edi],cl
        ret     0
        align   4
  .bins:db      '0000'
        db      '0001'
        db      '0010'
        db      '0011'
        db      '0100'
        db      '0101'
        db      '0110'
        db      '0111'
        db      '1000'
        db      '1001'
        db      '1010'
        db      '1011'
        db      '1100'
        db      '1101'
        db      '1110'
        db      '1111'

  .88:  ;add     esi,7
        mov     cx,0000'0000b shl 8 + 8  ;no dummies, show eight bytes
        jmp     bin_
  .84:  ;add     esi,7
        mov     cx,1000'1000b shl 8 + 8  ;dummy after each 4 bytes shown, show eight bytes
        jmp     bin_
  .82:  ;add     esi,7
        mov     cx,1010'1010b shl 8 + 8
        jmp     bin_
  .81:  ;add     esi,7
        mov     cx,1111'1111b shl 8 + 8
        jmp     bin_

  .44:  add     esi,3
        mov     cx,0000'0000b shl 8 + 4  ;no dummies, show four bytes
        jmp     bin
  .42:  add     esi,3
        mov     cx,1010'1010b shl 8 + 4  ;dummy after each 2 bytes shown, show four bytes
        jmp     bin
  .41:  add     esi,3
        mov     cx,1111'1111b shl 8 + 4
        jmp     bin

  .22:  inc     esi
        mov     cx,0000'0000b shl 8 + 2  ;no dummies, show 2 bytes
        jmp     bin
  .21:  inc     esi
        mov     cx,1111'1111b shl 8 + 2  ;dummy after each byte shown, show 2 bytes
        jmp     bin

  .11:  mov     cl,1;mov     cx,0000'0000b shl 8 + 1
        jmp     bin




sdec:
  .88:  mov     eax,[esi+4]
        mov     esi,[esi]
        test    eax,eax
        jns     _dec.88_
        neg     esi
        not     eax
        sbb     eax,-1
        mov     byte[edi],"-"
        inc     edi
        jmp     _dec.88_

  .44:  mov     esi,[esi]
        test    esi,esi
        jns     _dec.44_
        neg     esi
        mov     byte[edi],"-"
        inc     edi
        jmp     _dec.44_

  .22:  movsx   esi,word[esi]
        test    esi,esi
        jns     _dec.22_
        neg     esi
        mov     byte[edi],"-"
        inc     edi
        jmp     _dec.22_

  .11:  movsx   esi,byte[esi]
        test    esi,esi
        jns     _dec.11_
        neg     esi
        mov     byte[edi],"-"
        inc     edi
        jmp     _dec.11_

dec__:  sub     eax,eax
dec_:   mov     ebx,10
        mov     [edi],bh
_dec:   sub     edx,edx
        div     ebx
        xchg    esi,eax
        div     ebx
        add     dl,"0"
        dec     edi
        mov     [edi],dl
        dec     cl
        jz      .ret
        xchg    esi,eax
        add     ch,0100'0000b
        jnc     _dec
        mov     ch,0100'0000b
        dec     edi
        mov     byte[edi],"'"
        jmp     _dec
  .ret: ret     0

  .88:  mov     eax,[esi+4]
        mov     esi,[esi]
  .88_: mov     cx,0100'0000b shl 8 + 20 ;dummy after aech trio, 20 divisions
        add     edi,20+6                 ;six dummies
        jmp     dec_

  .44:  ;sub     eax,eax
        mov     esi,[esi]
  .44_: mov     cx,0100'0000b shl 8 + 10
        add     edi,10+3
        jmp     dec__

  .22:  ;sub     eax,eax
        movzx   esi,word[esi]
  .22_: mov     cx,0100'0000b shl 8 + 5
        add     edi,5+1
        jmp     dec__

  .11:  ;sub     eax,eax
        movzx   esi,byte[esi]
  .11_: mov     cx,0100'0000b shl 8 + 3
        add     edi,3
        jmp     dec__




hex_:   add     esi,7
hex:    std
        lodsb
        cld
        ror     eax,4
        call    daa_
        stosb
        rol     eax,4
        call    daa_
        stosb
        dec     cl
        jz      .ret
        shr     ch,1
        jnc     hex
        mov     al,"'"
        stosb
        jmp     hex
  .ret: mov     [edi],cl
        ret     0

  .88:  ;add     esi,7
        mov     cx,0000'0000b shl 8 + 8  ;no dummies, eight bytes
        jmp     hex_
  .84:  ;add     esi,7
        mov     cx,1000'1000b shl 8 + 8  ;dummy after each 4 bytes shown, 8 bytes
        jmp     hex_
  .82:  ;add     esi,7
        mov     cx,1010'1010b shl 8 + 8
        jmp     hex_
  .81:  ;add     esi,7
        mov     cx,1111'1111b shl 8 + 8
        jmp     hex_

  .44:  add     esi,3
        mov     cx,0000'0000b shl 8 + 4  ;no dummies, 4 bytes
        jmp     hex
  .42:  add     esi,3
        mov     cx,1010'1010b shl 8 + 4  ;dummy after each 2 bytes shown, 4 bytes
        jmp     hex
  .41:  add     esi,3
        mov     cx,1111'1111b shl 8 + 4
        jmp     hex

  .22:  inc     esi
        mov     cx,0000'0000b shl 8 + 2  ;no dummies, 2 bytes
        jmp     hex
  .21:  inc     esi
        mov     cx,1111'1111b shl 8 + 2  ;dummy after a byte shown, 2 bytes
        jmp     hex

  .11:  mov     cl,1;mov     cx,0000'0000b shl 8 + 1
        jmp     hex
    


simple interface added:


Description:
Filesize: 5.15 KB
Viewed: 6326 Time(s)

calc.PNG


Post 23 Jul 2011, 08:20
View user's profile Send private message Reply with quote
idle



Joined: 06 Jan 2011
Posts: 440
Location: Ukraine
idle 31 Jul 2011, 15:23
Code:
-binary view of dword and qword floats added
-asis.aa displays ten bytes of result
-meeting invisible chars, asis dumper adds "{contains invisible}"
-shift+enter add to history, respective button removed
-did not push last param in calls to CreateFile
-mode select combo removed, program stores tbytes if not 'q'/'Q' prefix
 precede numbers with 'q' or 'Q' to store those qwords, tbytes else
 qword operators can be used in tbyte mode - names conflict solved
-(new) tbyte operators:
 lwi,fildw, ldi,fildd, lqi,fildq load word,dword,qword integers
 ld,fldd, lq,fldq load floats in dword and qword formats
 sd,fstd sq,fstq store tbytes in dword and qword formats
 hyp,hypotenuse to compute hypotenuse
 leg,cathetus contrary hypotenuse
 log takes arbitrary base logarithm
 pipi makes fun, equals pi+pi
 sin,cos, see comments inside
 sqrt, same as ^0.5
-to insert comments use '{' & '}', if '}' is absent comment follows the end
-SMSW(see posts over) unresolved
-adding SSE is not difficult
    


Description:
Filesize: 8.24 KB
Viewed: 6231 Time(s)

calc.png


Post 31 Jul 2011, 15:23
View user's profile Send private message Reply with quote
Display posts from previous:
Post new topic Reply to topic

Jump to:  


< Last Thread | Next Thread >
Forum Rules:
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum
You cannot attach files in this forum
You can download files in this forum


Copyright © 1999-2024, Tomasz Grysztar. Also on GitHub, YouTube.

Website powered by rwasa.