Category : Utilities for DOS and Windows Machines
Archive   : HILOAD.ZIP
Filename : HILOAD.ASM

 
Output of file : HILOAD.ASM contained in archive : HILOAD.ZIP

;Equates

CR EQU 0D
LF EQU 0A
SPACE EQU 020
MON EQU MOV ;COMMON TYPO
ONE EQU 1
TWO EQU 2
DOLLAR EQU 024
ZERO EQU 0
BELL EQU 07


;Macros


PRINT macro ;USAGE: PRINT MSG1
push ax ;ALL REGISTERS PRESERVED
push dx
mov ah,9
lea dx, #1
int 021
pop dx
pop ax
#em

PRINT$ macro ;USAGE: PRINT$,"MESSAGE"
push ax ;PRINTS AT CURRENT CURSOR POSITION
push dx
JMP >M1
M0 DB #1
db "$"
M1: mov ah,9 ;ALL REGISTERS PRESERVED
lea dx,m0
int 021
pop dx
pop ax
#em


QUIT MACRO ;USAGE: QUIT 0
MOV AH,04C ;MUST GIVE SOME VALUE
MOV AL,#1
INT 021
#EM

NEWLINE macro ;equivalent to cr,lf
push ax ;scrolls if off screen
push dx
jmp > m1
m0 db 0d,0a,'$'
m1: lea dx,m0
mov ah,9
int 021
pop dx
pop ax
#em

SPLIT macro aam 16 #em ;be careful with these with
;NEC V-20/V-30 chips!
;UNSPLIT macro aad 16 #em ;This one causes problems w/V20+30
UNSPLIT macro ;This macro will effectively
push cx ;do the same thing, and should be
mov cx,4 ;compatible with all PC's
rol ah,cl
and ah,0f0
or al,ah
pop cx
#em

HEX_TO_PRNT macro ;changes an 8-bit register quantity
or #1,030 ;from 0-F to the ASCII equivalent
cmp #1,039 ;register must be in form 00 to 0F
if a add #1,7
#em

PRINT_REG macro ;used to print a register (or any 16-bit
jmp > m1 ;quantity) at the current cursor position
m0 db 5 dup ('$')
m1: push ax ;Usage - print_reg ax
mov ax,#1 ;prints the 16-bit quantity in HEX
xchg ah,al
push ax
make_hex_ascii
xchg ah,al
mov w[m0],ax
pop ax
xchg ah,al
make_hex_ascii
xchg ah,al
mov w[m0+2],ax
print m0
pop ax
#em

PRINT_32_DEC macro ;macro to print a 32-bit hex number
push ax ;as a decimal string
push dx ;enter with SI pointing to two-word
push di ;(four byte) quantity to be converted
mov dx,w[si] ;most significant word first
mov ax,w[si+2] ;prints at current cursor position
jmp > m1 ;all registers restored
m0 db 11 dup ('$')
m1: lea di,m0
add di,9
call large_hex_to_ascii
mov dx,di
mov ah,9
int 021
pop di
pop dx
pop ax
#em

REG_TO_PRINT MACRO ;converts a 16-bit quantity to ASCII
PUSH AX ;and puts the resultant string in a
PUSH BX ;place pointed to by DS:SI
MOV BX,#1 ;all registers restored
MOV AL,BH
CALL HEX2PRNT
MOV [SI],AX
MOV AL,BL
CALL HEX2PRNT
MOV [SI+2],AX
POP BX
POP AX
#EM


MAKE_CAP macro ;makes letters capitals
cmp #1,061 ;useage make_cap ah
jb > m1 ;AH contains a candidate ASCII letter
cmp #1,07A ;from a-z or A-Z
ja > m1 ;returns A-Z

and #1,0DF
m1: nop
#em


MAKE_HEX_ASCII macro ;makes AL in hex into two ASCII
split ;characters in AH:AL
hex_to_prnt ah
hex_to_prnt al
#em



;
; This is version 1.01 of HILOAD
; See accompanying .DOC file for theory of
; operation and instructions
;
; No guarantees, but the author would appreciate
; information on bugs.
;
; L. Shannon 5/18/89
;
org 0100
hiload: jmp long > l0

copyright db 'Copyright 1989 by L. Shannon'

load_block dw 0,0
FILE_STRING DB 65 DUP('$')
tail_ptr dw 0
file_ptr dw 0
old_int_27 dw 0,0
old_int_21 dw 0,0
start_addr dw 0100,0
tail_bfr db 127 dup ('020')
sw2127 db 0
tempwrds dw 0,0
bar db 40 dup ('*'),'$'
reset_msg db cr,lf,'Resetting ICA area',cr,lf,'$'
default_env db 'HILOAD',0
int_msg db 'Interupt '
int_num db 0,0,'H is now located at '
int_seg db 0,0,0,0,':'
int_off db 0,0,0,0,cr,lf,'$'
temp dw 0
load_point dw 0,0
lp_plus_bytes dw 0,0
int_addr_1 dw 0
int_addr_2 dw 0

new_int21: cmp ah,031 ;new address for INT 21H
je > z21 ;is it TSR termination?
cmp ax,02521 ;setting vector for INT 21H?
je > z25 ;if so, save it
cmp ax,03521 ;request for INT 21H address?
je > z35 ;if so, give him original address
cs jmp d[old_int_21] ;otherwise, do real INT 21H

z25:
cs mov old_int_21,dx ;here we save INT 21H address info
cs mov old_int_21+2,ds
iret ;and return to caller

z35: cs mov bx,[old_int_21] ;here we give him original address
cs mov es,[old_int_21+2]
iret ;and return to caller
z21: cs mov sw2127,0 ;exiting via INT 21 - set switch for
jmp > z22 ;storage return handling
new_int27: cs mov sw2127,1 ;trap for INT 27H - set switch
z22: mov ax,cs ;get our code segment
mov bx,dx ;save return size info
mov ds,ax ;set up local addressability
mov es,ax ;make sure other registers are
mov ss,ax ;what they should be
mov dx,[old_int_27] ;find original address of INT 27H
mov ax,[old_int_27+2] ;segment portion
mov es,0 ;addressing bottom page
es mov w[09c],dx ;store vector addresses directly
es mov w[09e],ax ;since INT 21H cannot be used to do
mov dx,[old_int_21] ;the job - we've trapped it above!
mov ax,[old_int_21 + 2] ;do the same with INT 21H
mov es,0
es mov w[084],dx ;and store its address in the
es mov w[086],ax ;proper place in the table
newline ;space a line
print$ 'Saved bytes = ' ;start of message
cmp sw2127,1 ;see how we terminated; 1=INT 27H so
je > q2 ;returns bytes - INT 21H returns para-
mov ax,bx ;graphs - here we're converting
xor dx,dx ;paragraphs to bytes by multiplying
mov cx,4 ;by 4 (shift left 4 places)
q1: rcl ax,1 ;have to allow for greater than 64K
pushf ;save flags with state of carry bit
rol dx,1
popf ;get flags back
adc dx,0 ;add in and include carry
loop q1 ;carry on
jmp > q3
q2: mov ax,bx ;size info in BX - do setup for
xor dx,dx ;conversion
q3: mov tempwrds,dx ;temporarily store upper and lower
mov tempwrds + 2,ax ;halves of return size info (32 bits)
push dx ;save DX
mov dx,[load_point] ;get where we started
MOV LP_PLUS_BYTES,dx ;put it here
pop dx ;retrieve DX
add lp_plus_bytes,dx ;add size info
MOV LP_PLUS_BYTES+2,AX ;store upper half here
lea si,tempwrds ;point to temporary storage
print_32_dec ;print out size in bytes
newline ;do new line
mov dx,[tempwrds] ;get back size info
mov ax,[tempwrds+2]
clc ;clear the carry
mov cx,4 ;we're going to convert to a 32-bit
q7: shr dx,1 ;number here and store it in
pushf ;the ICA area
rcr ax,1
popf
loop q7
mov es,040 ;point to segment of ICA
es mov bx,[0f0] ;get what was there
add dx,bx ;add new size
es mov [0f0],dx ;and put it back
es mov bx,[0f2] ;get old lower half
add ax,bx ;add new bytes saved data
inc ax ;allow for truncation
es mov [0f2],ax ;and put it back

newline ;start of trap info
print$ 'This TSR traps the following interrupts:'
newline ;some spaces
newline
;
; Here is where we look to see what interrupts are trapped
;
mov cx,0ff ;look at 256 interrupts
mov ax,03500 ;set up call
h1: push cx ;save registers
push ax
int 021 ;get interrupt addresses
mov ax,bx ;AX is offset
mov dx,es ;DX:AX is addr of interrupt
mov int_addr_1,ax ;store offset away
mov int_addr_2,dx ;store segment
call add_seg_off ;convert to 32-bit number
xchg bx,dx ;now BX:CX is int addr
xchg cx,ax ; in 32-bit form
mov dx,[load_point] ;where do we start
xor ax,ax ;no offset from start
call add_seg_off ;make 32-bitter
call cmp_32 ;is int address beyond start point?
jnc > h2 ;if below, can't be us - get out
mov dx,[lp_plus_bytes]
mov ax,[lp_plus_bytes + 2] ;DX:AX now address of end of pgm
call add_seg_off ;make 32-bits
call cmp_32 ;compare them
jc > h2 ;if greater - beyond me
pop ax ;we got one - retrieve interrupt
push ax ;and save function and int number
call hex2prnt ;get interrupt number in ASCII
lea si,int_num ;point to proper place
mov w[si],ax ;store it
lea si,int_seg ;point to place
reg_to_print [int_addr_2] ;get segment in ASCII
lea si,int_off ;point to place
reg_to_print [int_addr_1] ;print offset in ASCII
print int_msg ;print whole message
h2: pop ax ;get registers back
inc ax
pop cx
dec cx
jcxz > h3 ;are we done?
jmp long h1 ;no - go back for more
h3: quit 0 ;we're done - exit
;
; Main program starts here
;
l0: newline ;give us some space
print bar ;print banner bar
newline ;another space
mov ah,[080] ;see if any comand tail
cmp ah,1
ja > l1
l00: mov es,040 ;if no tail, reset ICA
es mov w[0f0],0
es mov w[0f2],0
print reset_msg ;write message
quit 0 ;and get out - normal exit

l1: mov di,080 ;point to command tail
l22: inc di
mov ah,[di]
cmp ah,020 ;bumping past the spaces here
je l22
mov file_ptr,di ;point to file name

L222: MOV AH,[DI]
CMP AH,SPACE
JE > L555
CMP AH,CR
JE > L555
INC DI
JMP L222

mov al,cr ;look for carriage return
mov cx,0100 ;look for a long time!
cld
repne scasb
jcxz l00 ;get out if no find one
dec di

L555:
mov tail_ptr,di ;save pointer to command tail
push di
lea bx,tail_bfr ;point to command tail (saved)
l16: mov ah,[di] ;get element
cmp ah,cr ;end of tail?
je > l17
mov [bx],ah ;stuff it away
inc di ;bump pointers
inc bx
jmp l16 ;do again
l17: mov b[bx],cr ;terminate tail
pop di

LEA BX,FILE_STRING ;point to buffer to store file name
MOV DI,[FILE_PTR] ;get pointer to program in command tail
L33: MOV AH,[DI] ;build the name, char by char
MAKE_CAP AH ;make sure all caps
MOV [BX],AH ;stuff it away
INC BX ;bump pointers
INC DI
CMP DI,[TAIL_PTR] ;are we done?
JB L33 ;if not, carry on
mov w[bx],'C.' ;stick in ".COM" extension
mov w[bx+2],'MO' ;reversed - that's the way Intel works
mov b[bx+4],0 ;end with 0 to make ASCIIZ string
lea dx,file_string ;point DX to the file
mov ah,04e ;find file
mov cx,027 ;file attribute byte - this works
int 021 ;do it
jc > l77 ;did we find it?
JMP LONG L78 ;got it! go process it
L77:
newline ;couldn't find file
newline
print$ 'Cant find file ';so say so

mov b[di-1],'$' ;put in string delimiter and print
print FILE_STRING ;what we were looking for
print$ ' ...ABORTING' ;sorry charlie
newline
newline
quit 3 ;quit with error level = 3

l78: mov al,' ' ;looking for a space
mov cx,100 ;up to 256 bytes back
std ;scan backwards
repne scasb ;and search
lea dx,file_string ;OK, now at start of file string
push di ;save pointer
mov b[di-1],0 ;make ASCIIZ string
push bx
push cx
mov ah,030 ;check DOS version level
int 021
pop cx
pop bx
cmp al,2 ;at least version 2?
jae > v1
newline ;if not, dump out
print$ 'Requires DOS 2.0 or above ... ABORTING'
newline
quit 2 ;bad DOS version - error level = 2

v1: cmp al,3 ;version 3.0 or above?
jae > v2 ;if it is, we're ok
lea si,default_env ;set up default envir var name
jmp > v3
v2: call whoami ;find out this programs'name
v3: call get_env_var ;get the environment value
jc > l88 ;did we get a match?
jmp long l888 ;yes, we did
l88: newline ;no we didn't
print$ 'No address given ... ABORTING'
quit 1 ;bad environment variable - error
;level = 1
l888: push ds
push es
pop ds
call asc_2_nums ;convert the ASCII to hex values
pop ds
mov start_addr+2,ax ;that's our starting address

mov es,040
es add ax,[0f0] ;add the last loads' space
es add ax,[0f2]
add ax,010 ;allow for PSP
mov load_block,ax ;this is out new loading address
sub ax,010 ;remove PSP allowance
newline ;starting load message
print$ 'Loading '
pop di
mov b[di-1],'$' ;make printable
print file_string ;and print it
print$ 'at segment '
print_reg ax ;print segment address
lea bx,load_block ;where we load
push es
push ds
pop es
mov ah,04b ;DOS EXEC function
mov al,3 ;load but don't execute
int 021 ;do it
pop es
mov ax,[load_block] ;loading address again
sub ax,010 ;allow for PSP
mov start_addr + 2,ax ;stuff it away
MOV LOAD_POINT,AX ;and here
MOV LP_PLUS_BYTES,AX ;and here, too
mov es,ax ;segment of where TSR is loaded
mov cx,0100 ;going to transfer 256 bytes
xor si,si ;of the PSP (we're using the one
xor di,di ;we got from DOS)
cld ;set direction flag
rep movsb ;transfer it

MOV DI,081 ;POINT TO COM TAIL IN NEW PSP
LEA SI,TAIL_BFR
XOR AL,AL ;COUNT OF COMMAND TAIL LENGTH
L98: MOV AH,[SI]
CMP AH,CR ;any command tail at all?
JE > L99
ES MOV [DI],AH ;if so, start transferring the
INC AL ;TSR's command tail - he might
INC DI ;need it
INC SI
JMP L98
L99: mov b[si],'$' ;again, for DOS INT 21H printing
newline
print$ 'Command tail = ' ;printing out the supplied
print tail_bfr ;command tail
mov b[si],cr ;terminate
ES MOV B[DI],CR ;terminate new tail
ES MOV [080],AL ;put in count
ES MOV B[081],SPACE ;and normal space
;
; Here we start revectoring the appropriate interrupts
;
mov ah,035 ;the 'gimme address' function
mov al,027 ;for interrupt 27H
int 021 ;go get it
mov ax,es ;its segment
mov old_int_27,bx ;store offset value
mov (old_int_27 + 2),ax ;store segment value

lea dx,new_int27 ;where we're going to point to
mov ah,025 ;tell DOS about it
mov al,027 ;for INT 27H
int 021 ;do it

mov ah,035 ;get address function again
mov al,021 ;this time for INT 21H
int 021 ;do it

mov ax,es
mov old_int_21,bx ;save offset
mov (old_int_21 + 2),ax ;and segment

lea dx,new_int21 ;point to my routine
mov ah,025 ;and tell DOS
mov al,021
int 021

mov ax,[start_addr+2] ;get address of routine
mov es,ax ;set up registers
mov ds,ax ;but don't change stack reg (SS)!!
cs jmp d[start_addr] ;and execute the program


;
; This is the end of the regular program.
; We exit when the TSR executes and INT 27H or an INT 21H with
; function 31H.
;
; The following are the various subroutines used
;

; routine to compare two 32-bit quantities
; if BX:CX > DX:AX, carry bit is set
; if BX:CX < DX:AX, carry bit is cleared
; if BX:CX = DX:AX, zero flag is set
;
; all registers unchanged
;

cmp_32: cmp bx,dx
jae > l0
jmp > l1
l0: ja > l2
cmp cx,ax
jb > l1
l2: stc
ret
l1: clc
ret

;
; routine to form 32-bit sum of (typically) a segment and
; offset pair
;
; enter with "segment" value in DX, "offset" in AX
; returns with sum in DX:AX
;
; all other registers restored
;
add_seg_off: push bx,cx
xor bx,bx
mov cx,4
l0: shl bx,1
shl dx,1
adc bx,0
loop l0
add ax,dx
adc bx,0
mov dx,bx
pop cx,bx
ret



;
; Routine to convert a HEX digit to a two byte word
; containing the equivalent ASCII characters
;
; Enter with the byte to be converted in AL
; Return with the ASCII string in AX in 'backwords' format
; i.e., an AL value of 47 would return AX = 3734
; so a MOV W[SI],AX for example would store the values
; in memory in the proper order
;
; All other registers restored
;
; This is essentially identical to the macro MAKE_HEX_ASCII
; except the macro does not interchange AH and AL
;
hex2prnt: xor ah,ah ;zero out upper half
aam 16 ;split into two
add ax,03030 ;make ASCII
cmp ah,039 ;check for A - F
if a add ah,7
cmp al,039
if a add al,7
xchg ah,al ;put in proper order
;for a MOV innstruction
ret



; routine to find out the program name.
; no parameters on entry.
; return with SI pointing to a string containing the file name
; with no extent or period.
; the string is terminated with a 0.
; all registers (except SI) are restored

WHOAMI: JMP > L0
MY_NAME DB 9 DUP (0)
L0: PUSH AX
PUSH BX
PUSH CX
PUSH ES
PUSH DI
MOV BX,[02C] ;GET SEG ADDR OF ENV
MOV ES,BX ;PUT IN ES
XOR DI,DI ;ZERO OUT DI
XOR AX,AX ;LOOKING FOR DOUBLE ZEROS
MOV CX,08000 ;MAX ENVIRONMENT LENGTH = 32K
CLD ;SET DIRECTION FLAG
L3: REPNE SCASB ;LOOK FOR ZERO
ES MOV BX,W[DI-1]
CMP BX,0 ;GOT TWO BYTES OF ZERO?
JNE L3
MOV AL,'.'
REPNE SCASB ;LOOKING FOR EXTENT
MOV BX,DI ;SAVE END OF STRING POINTER
L6: ES MOV AL,[DI]
CMP AL,'\'
JE > L7
CMP AL,0
JE > L7
DEC DI
JMP L6
L7: MOV SI,DI
INC SI ;POINT TO FIRST BYTE OF ASCIIZ
LEA DI,MY_NAME ;WILL STORE IT IN THIS SEGMENT
L2: ES MOV AH,[SI]
CMP AH,'.'
JE > L1
make_cap ah ;make sure all names are capitals
MOV [DI],AH
INC DI
INC SI
JMP L2
L1: LEA SI,MY_NAME
POP DI
POP ES
POP CX
POP BX
POP AX
RET






; Routine to find a match between a given string and an
; environment variable.
;
; Enter with DS:SI pointing to a string, terminated by a 0,
; which contains the string to be matched.
;
; Returns with SI pointing to the end of the matching
; string in in the environment.
;
; The environment variables are of the form NAME=string
; This routine returns SI pointing to the string, just
; after the equal sign.
;
; ES points to the environment segment on return
;
; If a matching string is found, the carry bit will be

; clear. If no match is found, the carry will be set.
;
; All other registers are restored; SI not guaranteed.

get_env_var:

jmp > l0
string_count dw 0

l0: push ax
push cx
push di
xor cx,cx ;zero out counter
push si ;save pointer
l1: mov al,[si]
cmp al,0 ;at end of string?
je > l2
inc si ;bump pointer
inc cx ;bump counter
jmp l1

l2: cs mov string_count,cx ;save counter
pop si ;restore pointer
call get_env_length ;get length of environment
mov cx,ax ;set up count
xor di,di ;start at beginning
mov ax,[02c] ;environment segment
mov es,ax
cld ;scan forward
mov al,[si] ;look for first letter
l3: repne scasb ;scan for it
dec di ;back off to point to match
jcxz > l99 ;get out if not there
push cx ;save counter
cs mov cx,[string_count]
push si ;save my old place
repe cmpsb ;see if they're all equal
pop si ;restore my place
jz > l4
;jcxz > l4 ;if zero, we got it
pop cx ;no match, so carry on
jmp l3
l99: stc ;set the carry
jmp > l5
l4: pop cx ;clear stack
mov si,di ;put pointer in SI
inc si ;skip past equal sign
clc ;clear carry
l5: pop di
pop cx
pop ax
ret


; routine to find length of environment
;
; IF CARRY IS CLEAR, RESULT RETURNED IN AX
; IF CARRY IS SET, ERROR CONDITION
;
; IN EITHER EVENT, ALL REGISTERS OTHER THAN AX ARE RESTORED
;
GET_ENV_LENGTH:
PUSH CX
PUSH ES
PUSH DI
MOV AX,[02C] ;GET SEGMENT OF ENVIRONMENT
MOV ES,AX
XOR DI,DI ;START AT BEGINNING OF ENV
MOV CX,08000 ;MAXIMUM ENV STRING = 32K
L9: ES MOV AX,W[DI]
CMP AX,0
JE > L0
INC DI
LOOP L9
JCXZ >L1 ;IF CX=0, WE'RE IN BIG TROUBLE
L0: MOV AX,DI ;SI IS LENGTH OF ENV - PUT IT IN AX
CLC ;CLEAR CARRY BIT - RESULT OK
JMP > L2
L1: STC ;SET THE CARRY - ERROR
L2: POP DI
POP ES
POP CX
RET



;
; Routine to convert a 2-digit ASCII pair into a hex number
; e.g., convert 3741 into 7A.
;
; Enter with the ASCII pair in AX, return with the hex digit
; in AL
;
; If all is well, the carry bit is clear
; If the carry bit is set, at least one of the proposed digits
; was not in the range (0-9) snd (A-F) (Routine accepts small
; letters and makes them caps)
;
; All other registers unaffected.
;
asc_2_hex: xchg ah,al
cmp ah,039
jbe > l0
and ah,0DF ;make caps
cmp ah,'F'
ja > l3
sub ah,7
l0: cmp ah,030
jb > l3
cmp al,039
jbe > l1
and al,0DF
cmp al,'F'
ja > l3
sub al,7
l1: cmp al,030
jb > l3
sub ax,03030
unsplit
clc
ret
l3: stc
ret

;
; Routine to convert a 4-digit ASCII number representation into
; a 4-digit hex number.
; e.g., 31374230 -> 17B0
;
; Enter with DS:SI pointing to the string.
; Return with the number in AX, in the proper order
; i.e., 31374230 -> AH = 17, AL = B0
;
; Carry bit set indicates bad ASCII number (out of range) see above
;
asc_2_nums: push bx
mov ax,w[si]
call asc_2_hex
jc > l1
mov bx,ax
mov ax,w[si+2]
call asc_2_hex
jc > l1
mov ah,bl
pop bx
clc
l1: ret

; ROUTINE TO CONVERT A 32-BIT NUMBER TO A DECIMAL ASCII STRING
; ENTER WITH THE NUMBER TO BE CONVERTED IN DX:AX
; AND DI POINTING TO THE LAST BYTE OF THE RESULT STRING AREA
; RETURN WITH DI POINTING TO FIRST NON-ZERO CHARACTER OF RESULTANT
; CONVERSION.
;
; BX, CX, and SI unchanged
;
; This routine was cribbed from FREE by Art Merrill - I don't really
; understand it all, but it works!

LARGE_HEX_TO_ASCII: PUSH BX
PUSH CX
XCHG CX,DX
MOV BX,10
L1: CMP CX,0
JE > L2
XCHG AX,CX
XOR DX,DX
DIV BX
XCHG AX,CX
DIV BX
OR DL,030
MOV [DI],DL
DEC DI
JMP L1
L2: XOR DX,DX
DIV BX
OR DL,030
MOV [DI],DL
DEC DI
CMP AX,0
JNE L2
inc di ;back up pointer to first char
POP CX
POP BX
RET

end


  3 Responses to “Category : Utilities for DOS and Windows Machines
Archive   : HILOAD.ZIP
Filename : HILOAD.ASM

  1. Very nice! Thank you for this wonderful archive. I wonder why I found it only now. Long live the BBS file archives!

  2. This is so awesome! 😀 I’d be cool if you could download an entire archive of this at once, though.

  3. But one thing that puzzles me is the “mtswslnkmcjklsdlsbdmMICROSOFT” string. There is an article about it here. It is definitely worth a read: http://www.os2museum.com/wp/mtswslnk/