home *** CD-ROM | disk | FTP | other *** search
- ;*************************************************************************
- ;
- ; Copyright 1982-1997 Pervasive Software Inc. All Rights Reserved
- ;
- ;*************************************************************************
- ;*************************************************************************
- ; COBBTRV.ASM
- ; This program is the interface between Micro Focus COBOL\2 programs and
- ; Btrieve. It is conditionally assembled to produce either
- ; 'cobrbtrv.obj' or 'cobpbtrv.obj', which are object modules for DOS &
- ; OS2, respectively.
- ;
- ; Calling Procedure from COBOL
- ; If using COBOL Animator (debugger) replace '_BTRV' with 'MF2BTRV'.
- ;
- ; CALL "_BTRV" USING FUNCTION, STATUS, POSITION-BLOCK, DATA-RECORD,
- ; 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-RECORD - 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)
- ;
- ; note: All numerical values passed to Btrieve as a parameter
- ; must be in the Intel format (LO-HIGH byte order). To
- ; do this define them as COMP-5.
- ;
- ;
- ; 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.
- ;
- ; For an OS2 module, define 'OS2=1' to your assembler. If you do
- ; not define OS2, then the assembled module will be for DOS.
- ; Examples of assembler switch: /DOS2=0 or /DOS2=1
- ;
- ; This module is current as of 06/07/94.
- ;
- ;*************************************************************************
- PUBLIC _BTRV
- ;*************************************************************************
- ; Define parameter offsets on stack
- ;*************************************************************************
- PARM_OFF = 6
- FUNCTION = PARM_OFF + 0
- STATUS = PARM_OFF + 4
- POS_BLK = PARM_OFF + 8
- DATA_REC = PARM_OFF + 12
- DATA_LEN = PARM_OFF + 16
- KEY_BUFFER = PARM_OFF + 20
- KEY_NUM = PARM_OFF + 24
- ;*************************************************************************
- ; 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
-
- ;*************************************************************************
- ; OS2 is defined on the assembler command line as 0 or 1.
- ;*************************************************************************
- IF OS2
- extrn BTRCALL:FAR
- ENDIF
-
- ;*************************************************************************
- ; Declare a data segment.
- ;*************************************************************************
- _XDATA segment word public 'DATA'
- BTRPARMS DB 28 DUP (?)
- USER_BUF STRUC
- 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
- USER_BUF ENDS
-
- _XDATA ENDS
-
- ;*************************************************************************
- ; Declare a code segment.
- ;*************************************************************************
- _TEXT segment word public 'CODE'
- assume cs:_TEXT
- assume ds:_XDATA
-
- ;*************************************************************************
- ; _BTRV
- ;*************************************************************************
- _BTRV proc far
- PUSH BP
- MOV BP,SP
- PUSH ES
- PUSH DS
- PUSH SI
-
- MOV DX,SEG _XDATA
- MOV DS,DX
-
- LEA SI,BTRPARMS
- IFE OS2 ;assembling for OS2 ?
- MOV AX,3500H + BTR_INT ; N
- INT 21H
- CMP BX,BTR_OFFSET
- JE LOADED ;Has Btrieve been initialized?
- LES BX,DWORD PTR [BP]+STATUS; N
- MOV AX,BTR_ERR
- MOV ES:[BX],AX
- JMP SHORT ERROUT
- ENDIF
- LOADED:
- ;get function parameter
- LES BX,DWORD PTR [BP]+FUNCTION ;get function address
- MOV CX,WORD PTR ES:[BX] ;get function number
- MOV [SI].USER_FUNCTION,CX
-
- ;get address of callers status word from parameter
- LES BX,DWORD PTR [BP]+STATUS ;get address of status word
- MOV WORD PTR [SI].USER_STAT_ADDR,BX
- MOV WORD PTR [SI].USER_STAT_ADDR+2,ES
-
- ;get position block
- LES BX,DWORD PTR [BP]+POS_BLK ; address of position block
- LEA AX,[BX]+FCB ;get diskette file block addr
- MOV WORD PTR [SI].USER_FCB_ADDR,AX
- MOV WORD PTR [SI].USER_FCB_ADDR+2,ES
- LEA AX,[BX]+CUR ;get currency block addr
- MOV WORD PTR [SI].USER_CUR_ADDR,AX
- MOV WORD PTR [SI].USER_CUR_ADDR+2,ES
-
- ;get data buffer
- LES BX,DWORD PTR [BP]+DATA_REC
- MOV WORD PTR [SI].USER_BUF_ADDR,BX
- MOV WORD PTR [SI].USER_BUF_ADDR+2,ES
-
- ;get data buffer length
- LES BX,[BP]+DATA_LEN ;get data length address
- MOV CX,WORD PTR ES:[BX] ;get data length
- MOV WORD PTR [SI].USER_BUF_LEN,CX
-
- ;get callers key buffer address and length
- LES BX,DWORD PTR [BP]+KEY_BUFFER ;get key buffer addr
- MOV WORD PTR [SI].USER_KEY_ADDR,BX
- MOV WORD PTR [SI].USER_KEY_ADDR+2,ES
- MOV BYTE PTR [SI].USER_KEY_LENGTH,255 ;set key length to max
-
- ;get key number parameter
- LES BX,DWORD PTR [BP]+KEY_NUM ;get key number address
- MOV CX,WORD PTR ES:[BX] ;get key number
- MOV BYTE PTR [SI].USER_KEY_NUMBER,CL
-
- ;set language and go process request
- MOV WORD PTR [SI].XFACE_ID,VAR_ID
- MOV DX,SI ;DX => user parms
-
- IFE OS2
- INT BTR_INT ;process request on DOS
- ELSE
- ;push parameters for OS/2 call and make call to Btrieve DLL
- MOV CX,WORD PTR [SI].USER_FUNCTION
- PUSH CX
- LES CX,DWORD PTR [SI].USER_FCB_ADDR
- PUSH ES
- PUSH CX
- LES CX,DWORD PTR [SI].USER_BUF_ADDR
- PUSH ES
- PUSH CX
- MOV CX,SI
- ADD CX,USER_BUF_LEN
- PUSH DS
- PUSH CX
- LES CX,DWORD PTR [SI].USER_KEY_ADDR
- PUSH ES
- PUSH CX
- SUB CX,CX
- MOV CL,BYTE PTR [SI].USER_KEY_LENGTH
- PUSH CX
- MOV CL,BYTE PTR [SI].USER_KEY_NUMBER
- PUSH CX
-
- CALL BTRCALL
-
- LES BX,DWORD PTR [SI].USER_STAT_ADDR ;get address of status
- MOV ES:[BX],AX ;Store Btrieve status
- ENDIF
- ;update data length as reported by Btrieve
- MOV CX,WORD PTR [SI].USER_BUF_LEN ;data length returned
- LES BX,[BP]+DATA_LEN ;address of data length
- MOV ES:[BX],CX ;set user's data length
- ERROUT:
- POP SI
- POP DS
- POP ES
- POP BP
- RET
- _BTRV endp
-
- _TEXT ends
- END