home *** CD-ROM | disk | FTP | other *** search
- ;***********************************************
- ; slide_.asm -- sliding dictionary with
- ; percolating update
- ;***********************************************
- page 0, 128
-
- include amscls.inc
- $_init GEN
-
- N = 2000h
- N2 = N * 2
- N4 = N * 4
-
- MAXMATCH = 256
- THRESHOLD = 3
-
- s1 segment at 0
- next label word
- s1 ends
-
- s2 segment at 0
- parent dw N2 dup(?)
- position dw (N + 256) dup(?)
- s2 ends
-
- s3 segment at 0
- prev dw N2 dup(?)
- level label byte
- childcount equ level + 1
- dw (N + 256) dup(?)
- s3 ends
-
- extrn error_:near
- extrn fwrite_crc_:near
- extrn fread_crc_:near
-
- EncodeOption struc
- output dw ?
- encode_start dw ?
- encode_end dw ?
- EncodeOption ends
-
- DecodeOption struc
- decode_c dw ?
- decode_p dw ?
- decode_start dw ?
- DecodeOption ends
-
- interfacing struc
- infile dw ?
- outfile dw ?
- original dd ?
- packed dd ?
- dicbit dw ?
- method dw ?
- blkcnt dw ?
- internal dw ?
- interfacing ends
-
- TEXT segment byte public 'CODE'
- extrn encode_start_fix_:near
- extrn encode_start_st1_:near
- extrn output_dyn_:near
- extrn output_st1_:near
- extrn encode_end_dyn_:near
- extrn encode_end_st1_:near
-
- extrn decode_start_dyn_:near
- extrn decode_start_fix_:near
- extrn decode_start_lz5_:near
- extrn decode_start_lzs_:near
- extrn decode_start_st0_:near
- extrn decode_start_st1_:near
- extrn decode_c_dyn_:near
- extrn decode_c_lz5_:near
- extrn decode_c_lzs_:near
- extrn decode_c_st0_:near
- extrn decode_c_st1_:near
- extrn decode_p_dyn_:near
- extrn decode_p_lz5_:near
- extrn decode_p_lzs_:near
- extrn decode_p_st0_:near
- extrn decode_p_st1_:near
- TEXT ends
-
- DATA segment word public 'DATA'
- public encode_define_
- encode_define_ DW output_dyn_
- DW encode_start_fix_
- DW encode_end_dyn_
-
- DW output_st1_
- DW encode_start_st1_
- DW encode_end_st1_
-
- public decode_define_
- decode_define_ DW decode_c_dyn_
- DW decode_p_st0_
- DW decode_start_fix_
-
- DW decode_c_dyn_
- DW decode_p_dyn_
- DW decode_start_dyn_
-
- DW decode_c_st0_
- DW decode_p_st0_
- DW decode_start_st0_
-
- DW decode_c_st1_
- DW decode_p_st1_
- DW decode_start_st1_
-
- DW decode_c_st1_
- DW decode_p_st1_
- DW decode_start_st1_
-
- DW decode_c_lzs_
- DW decode_p_lzs_
- DW decode_start_lzs_
-
- DW decode_c_lz5_
- DW decode_p_lz5_
- DW decode_start_lz5_
- DATA ends
-
-
- BSS segment word public 'DATA'
- public encode_set_
- public decode_set_
- encode_set_ dw 3 dup (?)
- decode_set_ dw 3 dup (?)
- count_ dw 2 dup(?)
- origsize_ dd 1 dup(?)
- compsize_ dd 1 dup(?)
- maxmatch_ dw 1 dup(?)
- dicbit_ dw 1 dup(?)
- unpackable_ dw 1 dup(?)
- matchlen dw 1 dup(?)
- matchpos dw 1 dup(?)
- lastmatchlen dw 1 dup(?)
- lastmatchpos dw 1 dup(?)
- seg1 dw 1 dup(?)
- seg2 dw 1 dup(?)
- seg3 dw 1 dup(?)
- avail dw 1 dup(?)
- pos dw 1 dup(?)
- remainder dw 1 dup(?)
- dicsiz dw 1 dup(?)
- dicsiz1 dw 1 dup(?)
- dicsiz2 dw 1 dup(?)
- dicsiz4 dw 1 dup(?)
- textend dw 1 dup(?)
-
- public maxmatch_
- public count_
- public matchlen
- public matchpos
- public lastmatchlen
- public lastmatchpos
- public seg1
- public seg2
- public seg3
- public avail
- public pos
- public remainder
- public dicbit_
- public origsize_
- public compsize_
- public unpackable_
-
- extrn text_:byte
- extrn buf_:dword
- extrn buf_limit_:word
- extrn MEMOVRERR_:byte
- extrn infile_:word
- extrn outfile_:word
- extrn crc_:word
-
- BSS ends
-
- CGROUP group TEXT
- DGROUP group DATA, BSS
-
- s0 equ DGROUP
- HASH1 equ (13 - 8 + 1)
-
- assume cs:TEXT, ds:DGROUP, es:nothing, ss:DGROUP
-
- TEXT segment byte public 'CODE'
-
- ; int encode_alloc(int method)
- public encode_alloc_
- encode_alloc_ proc near
- cld
- push ds
- pop es
-
- push cx
- push si
- push di
-
- push ax
- mov si, offset encode_define_ + 6;
- mov maxmatch_, 256
- mov dicbit_, 13
- mov dicsiz, 2000h
- $_if <cmp ax, 1>, E
- sub si, 6
- mov maxmatch_, 60
- dec dicbit_
- shr dicsiz, 1
- $_endif
- mov di, offset DGROUP:encode_set_
- mov cx, 3
- rep movsw
- $_if <cmp dicbit_, 13>, E
-
- SEG_SIZE1 = 2000h * 3 * 2 / 16
- SEG_SIZE2 = (2000h * 3 + 256) * 2 / 16
- SEG_SIZE3 = (2000h * 3 + 256) * 2 / 16
-
- mov bx, 0ffffh
- mov ah, 48h ; AllocMem
- int 21h
- $_if <cmp bx, SEG_SIZE1 + SEG_SIZE2 + SEG_SIZE3 + 256>, AE
- $_if <cmp bx, SEG_SIZE1 + SEG_SIZE2 + SEG_SIZE3 + 1024>, A
- mov bx, SEG_SIZE1 + SEG_SIZE2 + SEG_SIZE3 + 1024
- $_endif
- mov ah, 48h ; AllocMem
- int 21h
- mov seg1, ax
- add ax, SEG_SIZE1
- mov seg2, ax
- add ax, SEG_SIZE2
- mov seg3, ax
- add ax, SEG_SIZE3
- mov word ptr buf_ + 2, ax
- mov word ptr buf_, 0
- sub bx, SEG_SIZE1 + SEG_SIZE2 + SEG_SIZE3
- mov cl, 4
- shl bx, cl
- sub bx, 24
- mov buf_limit_, bx
- pop ax
-
- pop di
- pop si
- pop cx
- ret
- $_endif
- dec dicbit_
- shr dicsiz, 1
- $_endif
-
- SEG_SIZE14 = 1000h * 4 * 2 / 16
- SEG_SIZE24 = 0e20h
-
- mov bx, SEG_SIZE14 + SEG_SIZE24
- mov ah, 48h ; AllocMem
- int 21h
- $_if , C
- mov ax, offset DGROUP:MEMOVRERR_
- xor bx, bx
- call error_
- $_endif
- mov seg1, ax
- add ax, SEG_SIZE14
- mov seg2, ax
- add ax, 0400h
- mov seg3, ax
- add ax, 0620h
- mov word ptr buf_ + 2, ax
- mov word ptr buf_, 0
-
- mov buf_limit_, 1e00h - 24
- pop ax
- $_if <cmp ax, 5>, E
- dec ax
- $_endif
- pop di
- pop si
- pop cx
- ret
- encode_alloc_ endp
-
- init_slide_ proc near
- cld
- push ds
- pop ds
-
- push cx
- push dx
- push di
-
- mov es, seg3
- mov di, dicsiz
- mov dx, di ; dx = dicsiz
- shl di, 1
- mov bx, di ; bx = dicsiz * 2
- mov dicsiz2, bx
- lea ax, text_[bx]
- mov textend, ax
-
- add di, offset s3:level
- mov cx, 256
- mov ax, 1
- rep stosw
-
- mov es, seg2
- mov di, bx
- add di, offset s2:position
- mov cx, 256
- xor ax, ax
- rep stosw
-
- mov avail, 2
-
- mov di, bx
- ; add di, offset s2:parent
- mov cx, dx
- rep stosw
-
- mov es, seg1
- shl bx, 1
- mov dicsiz4, bx ; bx = dicsiz * 4
- mov di, bx
- ; add di, offset s1:next
- mov cx, N
- rep stosw
-
- ; mov di, offset s1:next
- mov di, ax
- mov cx, dicsiz
- $_do
- add ax, 2
- stosw
- $_until <LOOP>
-
-
- pop di
- pop dx
- pop cx
- ret
- init_slide_ endp
-
- ReadBuffer:
- ;===============================
- assume ds:s0, es:s0
- ;===============================
- push ds
- pop es
-
- push bx
- mov di, offset DGROUP:text_
- mov bx, dicsiz
- lea si, [di + bx]
- mov bp, si
- mov cx, maxmatch_
- add cx, bx
- shr cx, 1
- rep movsw
-
- mov ax, di
- mov cx, infile_
- call fread_crc_
-
- add remainder, ax
- $_if <or ax, ax>, NZ
- call dispmark1_
- $_endif
- pop bx
- mov ax, dicsiz
- shl ax, 1
- mov s0:pos, ax
- jmp DeleteInsert
-
- GetNextMatch proc near
- ;===============================
- assume ds:s0, es:nothing
- ;===============================
- dec remainder
- add s0:pos, 2
- inc bp
- cmp bp, textend
- je ReadBuffer
- GetNextMatch endp
-
- DeleteInsert proc near
- DeleteNode:
- public DeleteNode
- ;=======================================
- assume ds:s0, es:nothing, ss:s0
- ;=======================================
- push ds
- mov di, s0:pos
- ;===============================
- mov ds, s0:seg2
- assume ds:s2, es:nothing
- ;===============================
- cmp word ptr s2:[di], 0
- je ToInsertNode
-
- ;===============================
- mov es, s0:seg1
- mov ds, s0:seg3
- assume ds:s3, es:s1
- ;===============================
- mov si, s3:[di]
- mov bx, s1:[di] ; bx = s, si = r, di = p
-
- mov s1:[si], bx
- mov s3:[bx], si
-
- xor si, si
- ;===============================
- mov ds, s0:seg2
- assume ds:s2, es:s1
- ;===============================
- xchg si, s2:[di]
- ;===============================
- mov es, s0:seg3
- assume ds:s2, es:s3
- ;===============================
- dec s3:childcount[si]
- cmp si, dicsiz2
- jae ToInsertNode
- mov al, s3:childcount[si]
- cmp al, 1
- $_if , A
- ToInsertNode:
- jmp InsertNode
- $_endif
-
- mov di, s2:position[si] ; bx = s, si = r, di = t
- and di, 7fffh
- push di
- $_if <cmp di, s0:pos>, AE
- sub di, dicsiz2
- $_endif
- mov bx, di
- mov di, s2:[si] ; bx = s, q = di
- mov cx, s2:position[di] ; cx = u
- $_if <or cx, cx>, S
- shl cx, 1
- $_do
- shr cx, 1
- $_if <cmp cx, s0:pos>, AE
- sub cx, dicsiz2
- $_endif
- $_if <cmp cx, bx>, A
- mov bx, cx
- $_endif
- mov cx, bx
- or cx, dicsiz2
- mov s2:position[di], cx
- mov di, s2:[di]
- mov cx, s2:position[di] ; cx = u
- $_until <shl cx, 1>, NC
- shr cx, 1
- $_endif
- $_if <cmp di, dicsiz2>, B
- $_if <cmp cx, s0:pos>, AE
- sub cx, dicsiz2
- $_endif
- $_if <cmp cx, bx>, A
- mov bx, cx
- $_endif
- or bx, dicsiz2
- or bx, 8000h
- mov s2:position[di], bx
- $_endif
- pop di
- mov dx, di
- ;===============================
- mov es, s0:seg1
- assume ds:s2, es:s1
- ;===============================
- $_if <cmp word ptr s2:[di], 0>, E
- $_do
- mov di, s1:[di]
- $_until <cmp word ptr s2:[di], 0>, NE
- $_endif
- $_do
- mov bx, di
- mov di, s2:[bx]
- $_until <cmp di, si>, E
-
- ;===============================
- mov ds, s0:seg3
- assume ds:s3, es:s1
- ;===============================
- mov dx, si
- mov si, s3:[bx] ; si = t, bx = s
- mov di, s1:[bx] ; di = u
- mov s1:[si], di
- mov s3:[di], si
- mov si, dx
-
- mov di, s3:[si] ; bx = s, si = r, di = t
- mov s1:[di], bx
- mov s3:[bx], di
-
- mov di, s1:[si]
- mov s3:[di], bx
- mov s1:[bx], di
-
- ;===============================
- mov ds, s0:seg2
- assume ds:s2, es:s1
- ;===============================
- if 0
- xor di, di
- xchg di, s2:[si]
- mov s2:[bx], di
- else
- mov di, s2:[si]
- mov s2:[bx], di
- mov word ptr s2:[si], 0
- endif
-
- mov dx, s0:avail
- mov s1:[si], dx
- mov s0:avail, si
-
- InsertNode:
- ;===============================
- assume ds:s2, es:nothing
- ;===============================
- mov dl, s0:[bp]
- xor dh, dh
- shl dx, 1
- or dx, dicsiz2
-
- mov ax, s0:matchlen
- $_if <cmp ax, 4>, GE ; LIMITLEN
- dec ax
- mov si, s0:matchpos
- sub si, offset s0:text_ - 1
- shl si, 1
- or si, dicsiz2
-
- ;===============================
- mov es, s0:seg1
- assume ds:s2, es:s1
- ;===============================
- mov di, s2:[si]
- $_if <or di, di>, Z
- $_do
- mov si, s1:[si]
- mov di, s2:[si]
- $_until <or di, di>, NZ
- $_endif
- ;===============================
- mov es, s0:seg3
- assume ds:s2, es:s3
- ;===============================
- $_if <cmp al, s3:level[di]>, NA
- $_do
- mov si, di
- mov di, s2:[si]
- $_until <cmp al, s3:level[di]>, A
- $_endif
- mov dx, di
-
- mov bx, di
- mov cx, s0:pos
- $_if <cmp word ptr s2:position[bx], 0>, L
- $_do
- mov s2:position[bx], cx
- mov bx, s2:[bx]
- $_until <cmp word ptr s2:position[bx], 0>, NL
- $_endif
- $_if <cmp bx, dicsiz2>, B
- or cx, 8000h
- mov s2:position[bx], cx
- $_endif
- jmp MatchNext
-
- $_endif
- ;===============================
- assume ds:s2, es:nothing
- ;===============================
- mov ax, 1
- mov s0:matchlen, ax
-
- InsertLoop:
- ;===============================
- assume ds:s2, es:nothing
- ;===============================
- mov si, ax
- mov bl, s0:[bp + si]
- ; xor bh, bh
- mov cl, HASH1
- shl bx, cl
- add bx, dx
- and bx, N2 - 2
- or bx, dicsiz4 ; bx = h, si = r, di = s
-
- ;===============================
- mov es, s0:seg1
- assume ds:s2, es:s1
- ;===============================
- mov s2:parent, dx
-
- mov si, bx
- $_do
- mov si, s1:[si]
- $_until <cmp s2:[si], dx>, E
-
- $_if <or si, si>, Z
- ;===============================
- assume ds:s2, es:s1
- ;===============================
- mov di, s0:pos
- mov s2:[di], dx
-
- mov si, di
- xchg si, s1:[bx] ; bx = h, si = s, di = p
- mov s1:[di], si
- ;===============================
- mov es, s0:seg3
- assume ds:s2, es:s3
- ;===============================
- mov s3:[di], bx
- mov s3:[si], di
- mov di, dx
- inc s3:childcount[di]
-
- pop ds
- ret
- $_endif
- inc ax
-
- ;===============================
- assume ds:s2, es:nothing
- ;===============================
- MatchNext:
- push si ; si = r
- mov cx, s0:maxmatch_
- cmp si, dicsiz2
- $_if , B
- ;===============================
- mov es, s0:seg3
- assume ds:s2, es:s3
- ;===============================
- mov cl, s3:level[si]
- xor ch, ch
- mov si, s2:position[si] ; si = matchpos, ax = matchlen
- and si, 7fffh
- $_endif
- ;===============================
- mov bx, ss
- mov ds, bx
- assume ds:s0, es:nothing
- ;===============================
- shr si, 1
- add si, offset s0:text_
- $_if <cmp si, bp>, AE
- sub si, dicsiz
- $_endif
- mov s0:matchpos, si
-
- sub cx, ax
- $_if ,NE
- ;===============================
- mov es, bx
- assume ds:s0, es:s0
- ;===============================
- mov di, bp
- add di, ax
- add si, ax
- add ax, cx
- repe cmpsb
- $_endif
- ;===============================
- assume ds:s0, es:nothing
- ;===============================
- pop si
- $_if , NE
- inc cx
- sub ax, cx
- $_endif
- mov s0:matchlen, ax
-
- jne divnode
-
- $_if <cmp ax, maxmatch_>, NE
- mov cx, s0:pos
- ;===============================
- mov ds, s0:seg2
- assume ds:s2, es:nothing
- ;===============================
- mov s2:position[si], cx
- mov dx, si
- jmp InsertLoop
-
- $_endif
-
- ;===============================
- mov es, s0:seg3
- assume ds:s0, es:s3
- ;===============================
- mov di, s0:pos ; bx = t, si = r, di = p
- mov bx, s3:[si]
- mov s3:[di], bx
- ;===============================
- mov ds, s0:seg1
- assume ds:s1, es:s3
- ;===============================
- mov s1:[bx], di
-
- mov bx, s1:[si]
- mov s1:[di], bx
- mov s3:[bx], di
-
- ;===============================
- mov es, s0:seg2
- assume ds:s1, es:s2
- ;===============================
- mov s2:[di], dx
- mov word ptr s2:[si], 0
- mov s1:[si], di
-
- pop ds
- ret
-
- ;===============================
- assume ds:s0, es:nothing
- ;===============================
- divnode:
- mov di, s0:avail
- mov cx, s0:pos
- ;===============================
- mov es, s0:seg1
- assume ds:s0, es:s1
- ;===============================
- mov bx, s1:[di]
- mov s0:avail, bx ; di = s, si = r, ax = matchlen
-
- ;===============================
- mov ds, s0:seg2
- assume ds:s2, es:s1
- ;===============================
- mov s2:position[di], cx
- mov s2:[di], dx
-
- mov bl, al
- mov bh, 2
- ;===============================
- mov ds, s0:seg3
- assume ds:s3, es:s1
- ;===============================
- mov word ptr s3:level[di], bx
-
- mov bx, s3:[si] ; di = s, si = r, bx = t
- mov s3:[di], bx
- mov s1:[bx], di
-
- mov bx, s1:[si]
- mov s1:[di], bx
- mov s3:[bx], di
-
- mov bx, s0:matchpos ; di = s
- add bx, ax
- mov bl, s0:[bx]
- ; xor bh, bh
- mov cl, HASH1
- shl bx, cl
- add bx, di
- and bx, N2 - 2
- or bx, dicsiz4 ; bx = h, si = r, di = s
-
- push di
- if 0
- mov di, si
- xchg di, s1:[bx] ; di = t
- mov s1:[si], di
- else
- mov di, s1:[bx] ; di = t
- mov s1:[bx], si
- mov s1:[si], di
- endif
-
- mov s3:[si], bx
- mov s3:[di], si
- pop di
- ;===============================
- mov ds, s0:seg2
- assume ds:s2, es:s1
- ;===============================
- mov s2:[si], di
-
- mov si, ax
- mov bl, s0:[bp + si]
- ; xor bh, bh
- mov cl, HASH1
- shl bx, cl
- add bx, di
- and bx, N2 - 2
- or bx, dicsiz4 ; bx = h, di = s
-
- mov si, s0:pos ; si = pos
- mov s2:[si], di ; = s
-
- mov dx, di
-
- ;===============================
- mov ds, s0:seg3
- assume ds:s3, es:s1
- ;===============================
- mov di, si
- xchg di, s1:[bx]
- mov s1:[si], di ; bx = h, si = pos, di = t
-
- mov s3:[si], bx
- mov s3:[di], si
-
- pop ds
- ret
- DeleteInsert endp
-
- assume ds:DGROUP, es:nothing
-
- ;=======================================
- public encode_
- encode_ proc near
- push cx
- push dx
- push si
- push di
- push bp
-
- push ax
- mov di, ax
- mov ax, infile[di]
- mov infile_, ax
-
- mov ax, outfile[di]
- mov outfile_, ax
-
- mov ax, word ptr original[di]
- mov bx, word ptr original + 2[di]
- mov word ptr origsize_, ax
- mov word ptr origsize_ + 2, bx
-
- mov word ptr compsize_, ax
- mov word ptr compsize_ + 2, bx
-
- xor ax, ax
- mov unpackable_, ax
- mov crc_, ax
-
- call init_slide_
- call word ptr encode_set_[encode_start]
-
- mov cx, dicsiz
- mov ax, cx
- dec ax
- mov dicsiz1, ax
-
- mov ax, cx
- add ax, maxmatch_
- mov bp, offset DGROUP:text_
- add bp, ax
- shl ax, 1
- mov pos, ax
-
- push ds
- pop es
-
- mov bx, cx
- mov di, bp
- shr cx, 1
- mov ax, ' '
- rep stosw
-
- mov ax, bp
- mov cx, infile_
- call fread_crc_
- mov remainder, ax
- $_if <or ax, ax>, NZ
- call dispmark1_
- $_endif
-
- mov matchlen, 0
- call DeleteInsert
-
- mov ax, remainder
- $_if <cmp matchlen, ax>, A
- mov matchlen, ax
- $_endif
- $_do
- $_break , <cmp remainder, 0>, E
- mov ax, matchlen
- mov lastmatchlen, ax
- mov ax, matchpos
- mov lastmatchpos, ax
- call GetNextMatch
- mov ax, remainder
- $_if <cmp matchlen, ax>, A
- mov matchlen, ax
- $_endif
-
- mov ax, lastmatchlen
- $_if <cmp matchlen, ax>, A, OR
- $_c <cmp ax, THRESHOLD>, B
- mov al, ss:[bp - 1]
- xor ah, ah
- call word ptr encode_set_[output]
- $_else
- mov bx, bp
- sub bx, lastmatchpos
- sub bx, 2
- and bx, dicsiz1
- add ax, 256 - THRESHOLD
- call word ptr encode_set_[output]
- dec lastmatchlen
- $_do
- call GetNextMatch
- $_until <dec lastmatchlen>, Z
- mov ax, remainder
- $_if <cmp matchlen, ax>, A
- mov matchlen, ax
- $_endif
- $_endif
- $_until <cmp unpackable_, 0>, NE
- call word ptr encode_set_[encode_end]
-
- pop di
- mov ax, word ptr origsize_
- mov bx, word ptr origsize_ + 2
- sub ax, word ptr compsize_
- sbb bx, word ptr compsize_ + 2
- mov word ptr packed[di], ax
- mov word ptr packed + 2[di], bx
- pop bp
- pop di
- pop si
- pop dx
- pop cx
- ret
- encode_ endp
-
-
- ;=======================================
- public decode_
- decode_ proc near
- cld
- push ds
- pop es
-
- push cx
- push dx
- push si
- push di
- push bp
-
- FILE struc
- mode db ?
- ptr dw ?
- rcount dw ?
- wcount dw ?
- base dw ?
- bufsiz dw ?
- fd dw ?
- smallbuf db ?
- FILE ends
-
- extrn _iob_:byte
- extrn use_:byte
-
- mov di, ax
-
- mov bx, infile[di]
- $_if <or bx, bx>, Z
- mov bx, offset DGROUP:_iob_ + 14 * 19
- mov mode[bx], 0b1h
- mov ax, internal[di]
- mov ptr[bx], ax
- mov rcount[bx], 1000h
- $_endif
- mov infile_, bx
-
- mov ax, outfile[di]
- mov outfile_, ax
-
- mov cx, dicbit[di]
- mov dicbit_, cx
- mov ax, 1
- shl ax, cl
- mov dicsiz, ax
-
- mov ax, word ptr original[di]
- mov word ptr origsize_, ax
-
- mov ax, word ptr original + 2[di]
- mov word ptr origsize_ + 2, ax
-
- mov ax, word ptr packed[di]
- mov word ptr compsize_, ax
-
- mov ax, word ptr packed + 2[di]
- mov word ptr compsize_ + 2, ax
-
- xor ax, ax
- mov count_, ax
- mov count_ + 2, ax
- mov crc_, ax
-
- mov si, method[di]
- mov dx, 100h - 3
- $_if <cmp si, 6>, E
- inc dx
- $_endif
-
- dec si
- mov di, si
- shl si, 1
- add si, di
- shl si, 1
- add si, offset DGROUP:decode_define_
- mov di, offset DGROUP:decode_set_
- mov cx, 3
- rep movsw
-
- mov di, offset DGROUP:text_
- mov cx, N
- mov ax, ' '
- rep stosw
-
- call word ptr decode_set_[decode_start]
-
- mov di, offset DGROUP:text_
- mov bp, dicsiz
- jmp $entry
-
- $_while <TRUE>
- $loop:
- call word ptr decode_set_[decode_c]
-
- $_if <or ah, ah>, Z
- stosb
- $_if <cmp di, offset DGROUP:text_[N2]>, E
- mov di, offset DGROUP:text_
- mov ax, di
- mov bx, N2
- mov cx, outfile_
- call fwrite_crc_
- $_endif
- add word ptr count_, 1
- adc word ptr count_ + 2, 0
- $entry:
- sub word ptr origsize_, 1
- sbb word ptr origsize_ + 2, 0
- dec bp
- jc $endloop
- jns $loop
-
- call dispmark2_
- $_else
- mov cx, ax
- sub cx, dx
- mov ax, di
- sub ax, offset DGROUP:text_
- call word ptr decode_set_[decode_p]
- mov si, di
- sub si, ax
- dec si
- add word ptr count_, cx
- adc word ptr count_ + 2, 0
- sub bp, cx
- $_if , S
- call dispmark2_
- $_endif
- mov ax, di
- add ax, cx
- push cx
- $_if <sub ax, offset s0:text_[N2]>, AE
- sub cx, ax
- rep movsb
- push ax
- mov di, offset DGROUP:text_
- mov ax, di
- mov bx, N2
- mov cx, outfile_
- call fwrite_crc_
- pop cx
- $_else
- $_if <cmp si, offset s0:text_>, B
- add si, N2
- $_endif
- $_endif
- mov ax, si
- add ax, cx
- $_if <sub ax, offset s0:text_[N2]>, AE
- sub cx, ax
- rep movsb
- mov cx, ax
- mov si, offset s0:text_
- $_endif
- rep movsb
- pop cx
- sub word ptr origsize_, cx
- sbb word ptr origsize_ + 2, 0
- jc $endloop
- $_endif
- $_enddo
- $endloop:
-
- mov ax, offset DGROUP:text_
- mov bx, di
- sub bx, ax
- mov cx, outfile_
- call fwrite_crc_
-
- inc bp
- $_if <cmp bp, dicsiz>, NE
- call dispmark2_
- $_endif
- pop bp
- pop di
- pop si
- pop dx
- pop cx
- ret
- decode_ endp
-
- public dispmark2_
- dispmark2_ proc near
- add bp, dicsiz
- dispmark2_ endp
-
- public dispmark1_
- dispmark1_ proc near
- mov al, 'o'
- jmp dispmark_
- dispmark1_ endp
-
- extrn dispmark_:near
- TEXT ends
-
- public init_slide_
- public DeleteInsert
- public GetNextMatch
- public encode_
- public decode_
-
- end
-