home *** CD-ROM | disk | FTP | other *** search
- ;*************************************************************************
- ;
- ; Copyright 1982-1997 Pervasive Software Inc. All Rights Reserved
- ;
- ;*************************************************************************
- ;*************************************************************************
- ; MF2BTRV.ASM
- ; This program is the interface between Micro Focus COBOL\2 animated
- ; programs and Btrieve. It is loaded by the COBOL runtime, and uses
- ; Intel byte-order.
- ;
- ; It is important to note that the COBOL\2 animator passes stack
- ; parameters from left to right, while the non-animated COBOL/2
- ; interface passes parameters from right to left. However, COBOL/2
- ; passes integers in the Intel hi-lo format for both animated and
- ; non-animated applications.
- ;
- ; Note that MF2BTRV.OBJ & CSUPPORT.OBJ have been dropped. Use
- ; COBRBTRV.OBJ in place of these.
- ;
- ; Calling Procedure from COBOL
- ; CALL "MF2BTRV" USING FUNCTION, STATUS, POSITION-BLOCK, DATA-BUFFER,
- ; DATA-LEN, KEY-VALUE, KEY-NUMBER.
- ; where
- ; FUNCTION - pointer to function PIC 9999 COMP-5 (hi-lo)
- ; STATUS - pointer to ret status PIC 9999 COMP-5 (hi-lo)
- ; POSITION-BLOCK - pointer to 128-byte position block
- ; DATA-BUFFER - pointer to data buffer
- ; DATA-LEN - pointer to length of data buffer
- ; KEY-VALUE - pointer to key buffer
- ; KEY-NUMBER - pointer to key number PIC 9999 COMP-5 (lo-hi)
- ;
- ; IMPORTANT
- ; ---------
- ; Pervasive Software Inc., invites you to modify this file
- ; if you find it necessary for your particular situation. However,
- ; we cannot provide technical support for this module if you
- ; do modify it.
- ;
- ;*************************************************************************
- PUBLIC _BTRV
- ;*************************************************************************
- ; Define parameter offsets on stack
- ;*************************************************************************
- PARM_OFF = 6
- FUNCTION = PARM_OFF + 24
- STATUS = PARM_OFF + 20
- POS_BLK = PARM_OFF + 16
- DATA_REC = PARM_OFF + 12
- DATA_LEN = PARM_OFF + 8
- KEY_BUFFER = PARM_OFF + 4
- KEY_NUM = PARM_OFF + 0
- ;*************************************************************************
- ; Define offets within position block where FCB and
- ; currency information are stored.
- ;*************************************************************************
- FCB EQU 0
- CUR EQU 38
- VAR_ID EQU 06176H ;Variable record interface id
- BTR_ERR EQU 20 ;status - Btrieve not initialized
- BTR_INT EQU 07BH
- BTR_OFFSET EQU 033H
- BTR_VECTOR EQU BTR_INT * 4 ;Absolute vector offset for interrupt
-
- ;*************************************************************************
- ; Code Segment
- ;*************************************************************************
- CODE SEGMENT 'CODE'
- ASSUME CS:CODE,DS:CODE
-
- _BTRV proc far
- jmp cob_0
-
- USER_BUF_ADDR DD ? ;callers data buffer offset
- USER_BUF_LEN DW ? ;length of callers data buffer
- USER_CUR_ADDR DD ? ;callers currency info offset
- USER_FCB_ADDR DD ? ;disk FCB for current request
- USER_FUNCTION DW ? ;requested function
- USER_KEY_ADDR DD ? ;callers key buffer offset
- USER_KEY_LENGTH DB ? ;length of key buffer
- USER_KEY_NUMBER DB ? ;key of reference for request
- USER_STAT_ADDR DD ? ;callers status word offset
- XFACE_ID DW ? ;language identifier
-
- cob_0: push bp
- mov bp,sp
- push es
- push ds
- push si
-
- ;set up to access data within this code segment
- push cs
- pop ds
-
- ;see if Btrieve has been initialized
- push es
- push bx
- mov ax,3500h + BTR_INT
- int 21h
- cmp bx,BTR_OFFSET
- pop bx
- pop es
- je cob_1 ;Has Btrieve been initialized?
- les si,dword ptr [bp]+STATUS ; N, BX = status offset
- mov ax,BTR_ERR
- mov es:[si],ax ;Set return status
- jmp cob_2 ;go to exit
- COB_1:
- ;get function parameter
- les si,dword ptr [bp]+FUNCTION ;get function address
- mov cx,es:[si] ;get function number
- mov USER_FUNCTION,cx
-
- ;get address of callers status word from parameter
- les cx,dword ptr [bp]+STATUS ;get address of status word
- mov word ptr USER_STAT_ADDR,cx
- mov word ptr USER_STAT_ADDR+2,es
-
- ;get position block
- les si,dword ptr [bp]+POS_BLK ;SI = address of position block
- lea ax,es:[si]+FCB ;get diskette file block addr
- mov word ptr USER_FCB_ADDR,ax
- mov word ptr USER_FCB_ADDR+2,es
- lea ax,es:[si]+CUR ;get currency block addr
- mov word ptr USER_CUR_ADDR,ax
- mov word ptr USER_CUR_ADDR+2,es
-
- ;get data buffer
- les si,dword ptr [bp]+DATA_REC
- mov word ptr USER_BUF_ADDR,si
- mov word ptr USER_BUF_ADDR+2,es
-
- ;get data buffer length
- les si,dword ptr [bp]+DATA_LEN ;get length address
- mov cx,es:[si] ;get length
- mov USER_BUF_LEN,cx
-
- ;get callers key buffer address and length
- les si,dword ptr [bp]+KEY_BUFFER ;get key buffer addr
- mov word ptr USER_KEY_ADDR,si
- mov word ptr USER_KEY_ADDR+2,es
- mov USER_KEY_LENGTH,255 ;set key length to max
-
- ;get key number parameter
- les si,dword ptr [bp]+KEY_NUM ;get key number address
- mov cx,es:[si] ;get key number
- mov USER_KEY_NUMBER,cl
-
- ;set language and go process request
- mov XFACE_ID,VAR_ID ;get interface id
- lea dx,USER_BUF_ADDR ;DX => user parms
-
- int BTR_INT ;process request
-
- mov cx,USER_BUF_LEN
- les si,dword ptr [bp]+DATA_LEN ;get length address
- mov es:[si],cx ;reset length in user's space
- COB_2:
- pop si
- pop ds
- pop es
- pop bp
- ret
- _BTRV ENDP
-
- CODE ENDS
- END
-