home *** CD-ROM | disk | FTP | other *** search
- ;*************************************************************************
- ;
- ; Copyright 1982-1997 Pervasive Software Inc. All Rights Reserved
- ;
- ;*************************************************************************
- ;*************************************************************************
- ; MFXBTRV.ASM
- ; This program interfaces between Micro Focus COBOL animated programs and
- ; Btrieve assembly routines. It is loaded as MFXBTRV.BIN by the COBOL
- ; runtime, and uses non-Intel byte order.
- ;
- ; Calling Procedure from COBOL:
- ; CALL "MFXBTRV" USING FUNCTION, STATUS, POSITION-BLOCK, DATA-BUFFER,
- ; DATA-LEN, KEY-VALUE, KEY-NUMBER.
- ; where
- ; FUNCTION - pointer to function PIC 9999 COMP-0 (hi-lo)
- ; STATUS - pointer to ret status PIC 9999 COMP-0 (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-0 (hi-lo)
- ;
- ; 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.
- ;
- ;*************************************************************************
- PAGE 60,132
- PUBLIC BTRV
- ;*************************************************************************
- ; Define parameter offsets from BX
- ;*************************************************************************
- 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
- ;*************************************************************************
- ; Define offets within position block where FCB and
- ; currency information are stored.
- ;*************************************************************************
- FCB = 0
- CUR = 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
- CREATE EQU 14 ;Create function call
- STAT EQU 15 ;Stat function call
- CREATE_SUPP EQU 31 ;Create supplemental index call
- ;*************************************************************************
- ; Code Segment
- ;*************************************************************************
- CODE SEGMENT 'CODE'
- ASSUME CS:CODE,DS:CODE
- ;*************************************************************************
- ; BTRV
- ;*************************************************************************
- 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
- XCHG AH,AL
- MOV ES:[SI],AX ;Set return status
- JMP COB_2 ;Skip interrupt since invalid
- COB_1:
- ;get function parameter
- LES SI,DWORD PTR [BP]+FUNCTION ;get function address
- MOV CX,ES:[SI] ;get function number
- XCHG CL,CH
- 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
- XCHG CL,CH
- 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,CH
-
- ;set language and go process request
- MOV XFACE_ID,VAR_ID ;get interface id
- LEA DX,USER_BUF_ADDR ;DX => user parms
- CALL PRE_SW
- INT BTR_INT ;process request
- CALL POST_SW
- MOV CX,USER_BUF_LEN
- XCHG CL,CH
- LES SI,DWORD PTR [BP]+DATA_LEN ;get length address
- MOV ES:[SI],CX ;reset length in user's space
- COB_2:
- LES SI,USER_STAT_ADDR
- MOV AX,ES:[SI]
- XCHG AH,AL
- MOV ES:[SI],AX
-
- POP SI
- POP DS
- POP ES
- POP BP
- RET
- BTRV ENDP
-
- ;*************************************************************************
- ; These routines are used to put the control blocks for CREATE, CREATE_SUPP,
- ; and STAT into a regular form. Cobol always reverses the high and low
- ; order byte in words.
- ;*************************************************************************
- POST_SW PROC NEAR
- CMP USER_FUNCTION,STAT ;if stat function
- JE POST_10 ; do switch
- PRE_SW LABEL NEAR
- CMP USER_FUNCTION,CREATE ;if create function then
- JE POST_10 ; do switch
- CMP USER_FUNCTION,CREATE_SUPP ;if not create supp,
- JNE POST_99 ; skip switch
- POST_10:
- PUSH AX
- PUSH BX
- PUSH CX
- PUSH DX
- PUSH SI
- PUSH DS
-
- MOV DX,USER_FUNCTION
- LDS BX,USER_BUF_ADDR ;BX => file structure
- PUSH BX ;save BX for later
- MOV CX,8 ;8 words in the header
- POST_20:
- MOV AX,[BX] ;get word
- XCHG AL,AH ;exchange bytes
- MOV [BX],AX ;replace word as COBOL expects it
- INC BX
- INC BX
- LOOP POST_20
- POP SI ;SI = old BX
- MOV CX,4[SI] ;cx = # keys
- CMP CH,0
- JE POST_25
- XCHG CL,CH
- POST_25:
- CMP CX,119 ;if > max indexex then
- JA POST_90 ; must be a bad specification
- CMP CX,0
- JE POST_90 ;Does this file have any keys?
- ; Y
- ;test for any segmented key specs
- PUSH BX ;BX -> 1st key spec
- SUB BX,16
- SUB AX,AX
- POST_27:
- INC AX
- ADD BX,16
- CMP DX,CREATE
- JNE POST_28
- TEST WORD PTR 4[BX],1000h ;Does this spec have another segment
- JNE POST_27 ; yes
- JMP SHORT POST_29
- POST_28:
- TEST WORD PTR 4[BX],0010h ;Does this spec have another segment
- JNE POST_27 ; yes
- POST_29:
- LOOP POST_27
- POP BX ;BX -> 1st key spec
- MOV CX,AX ;CX = real number of key specs
-
- ;now switch the total number of key specs
- MOV AL,8 ;number of words in key spec
- MUL CL
- MOV CX,AX ;CX = number of words in key specs
- POST_30:
- MOV AX,[BX] ;get word
- XCHG AL,AH ;exchange bytes
- MOV [BX],AX ;replace word as COBOL expects it
- INC BX
- INC BX
- LOOP POST_30
- POST_90:
- POP DS
- POP SI
- POP DX
- POP CX
- POP BX
- POP AX
- POST_99:
- RET
- POST_SW ENDP
-
- CODE ENDS
- END