[Search for users] [Overall Top Noters] [List of all Conferences] [Download this site]

Conference orarep::nomahs::dbintegrator_public_public

Title:DB Integrator Public Conference
Notice:Database Integration - today! Kit/Doc info see note 36
Moderator:BROKE::ABUGOV
Created:Mon Sep 21 1992
Last Modified:Fri Jun 06 1997
Last Successful Update:Fri Jun 06 1997
Number of topics:1171
Total number of notes:5187

1050.0. "DBI GW for ORACLE IVP failure?" by ORAREP::GIDDAY::REINHOLD (Skippy) Tue Apr 23 1996 05:51

    Gidday,
           I have a customer who is trying to install DBI GW for ORACLE,
    and the backup bombed out with a failure (which had a solution in the
    release notes to rebuild some images), and continued the installation.
    The IVP now fails with the following error message.
    
    %SQL-E-SETVER SYS$COMMON:[SYSLIB]SQL$SHR.EXE Image Ident Problem
    %SQL-E-SETVER IMAGE IDENT = 6.1, VERSION = 6.0
    
    
    He is running an ALPHA with VMS V6.2 and DBI GW V3.1 for ORACLE
    			And RDB V6.1
    
    By setting Verify, it seems to be failing with,
    
    $       !
    $       ! Validate that the image ident matches the image name for $
        ! Multiversion image. $       ! $       IF (P1 .NES. "S") .AND.
    (P1 .NES. "") $       THEN $           IF "6.0" .NES. "6.1" $
     THEN $               WRITE SYS$OUTPUT " "
    
    $               WRITE SYS$OUTPUT "%SQL-E-SETVER
    SYS$COMMON:[SYSLIB]SQL$SHR.EXE Imag e Ident Problem" %SQL-E-SETVER
    SYS$COMMON:[SYSLIB]SQL$SHR.EXE Image Ident Problem $
    WRITE SYS$OUTPUT "%SQL-E-SETVER IMAGE IDENT = " + -
                        "6.1, VERSION = 6.0"
    %SQL-E-SETVER IMAGE IDENT = 6.1, VERSION = 6.0
    $               WRITE SYS$OUTPUT " "
    $               CALL CLEANUP_RTN
    $ CLEANUP_RTN: SUBROUTINE
    
    
    
    
    	Does anyone have any ideas?
    
    					Cheers,
    						Dave Reinhold,
    						Digital CSC,
    						Sydney, Australia.
    
    
    
    The IVP, Followd by the IVP executed with verify.
    
    $!
    --------------------------------------------------------------------------
    $!   c Digital Equipment Corporation 1993,1994. All rights reserved.
    $!
    $!   Restricted Rights: Use, duplication, or disclosure by the U.S.
    $!   Government is subject to restrictions as set forth in subparagraph
    $!   (c) (1) (ii) of DFARS 252.227-7013, or in FAR 52.227-19, or in FAR
    $!   52.227-14 Alt. III, as applicable.
    $!
    $!   This software is proprietary to and embodies the confidential
    $!   technology of Digital Equipment Corporation. Possession, use, or
    $!   copying of this software and media is authorized only pursuant to
    a
    $!   valid written license from Digital or an authorized sublicensor.
    $!
    --------------------------------------------------------------------------
    $!++
    $!  Facility:
    $!      LINK
    $!
    $!  Module:
    $!      LDRV$IVP.COM
    $!
    $!  Product:
    $!      LEDA031     (Product Name)
    $!      LSYB031     (Product Name)
    $!      LORA031     (Product Name)
    $!      LDB2030     (Product Name)
    $!      LSQK031     (Product Name)
    $!
    $!  Abstract:
    $!      This is an installation verification procedure (IVP). It checks
    the
    $!      installation of a DEC DB Integrator Gateway for EDA/SQL Sybase,
    Oracle,
    $!      DB2, and SequeLink.
    $!
    $!  Parameters:
    $!
    $!      None
    $!
    $!  Environment:
    $!      This file is expected to be named LEDA$IVP.COM, LSYB$IVP.COM,
    $!      LORA$IVP.COM, LDB2$IVP.COM, or LSQK$IVP.COM.
    $!      The routine setup_gateway_strings is dependent on the first 4
    $!      characters of the filename.
    $!
    $!++
    $   on warning   then goto ldrv_ivp_warning
    $   on control_y then goto ldrv_ivp_interrupt
    $   !
    $ say := "write sys$output"
    $
    $!
    $   gosub setup_gateway_strings
    $!
    $   say " "
    $   say "
    *****************************************************************"
    $   say " "
    $   say "               Installation Verification Procedure (IVP) for
    $   say "               ''gateway_full_name' ''gateway_version'"
    $   say "                        for ''operating_system'
    $   say " "
    $   say "    Copyright Digital Equipment Corporation 1993,1994. All rights rese
    $   say " "
    $   say "    This IVP verifies that all the gateway images are in place
    and"
    $   say "    a simple query can be executed. "
    $   say " "
    $   say "
    *****************************************************************"
    $   say " "
    $   say ""
    $   say "Enter a SQL attach string terminated by a semi-colon."
    $   say "Example:"
    $   say "''gateway_example_attach'"
    $
    $   ! issue case-sensitive message if it's SYBASE
    $   if "''gateway_id'" .EQS. "LSYB"
    $   then
    $       say " "
    $       say "If the SYBASE database is case sensitive, then you must specify"
    $       say "the attach qualifier values just as you would enter them if you"
    $       say "were working directly with the SYBASE database."
    $       say " "
    $   endif
    $!
    $ldrv_ivp_reset_attach_string:
    $   ldrv_ivp_attach_string =""
    $   ldrv_ivp_prompt = "attach string: "
    $!
    $ldrv_ivp_get_attach_string:
    $   read /prompt="''ldrv_ivp_prompt'" sys$command ldrv_ivp_attach
    $   ldrv_ivp_prompt = "_: "
    $   ldrv_ivp_attach = f$edit(ldrv_ivp_attach, "trim")
    $   if f$extract(f$length(ldrv_ivp_attach)-1,1,
    ldrv_ivp_attach).eqs.";" then goto ldrv_ivp_got_attach_string
    $   ldrv_ivp_attach_string =  ldrv_ivp_attach_string +
    ldrv_ivp_attach
    $   goto ldrv_ivp_get_attach_string
    $!
    $ldrv_ivp_got_attach_string:
    $   ldrv_ivp_attach_string =  ldrv_ivp_attach_string +
    f$extract(0,f$length(ldrv_ivp_attach)-1, ldrv_ivp_attach)
    $   say ""
    $   say "The current string is: "
    $   say ldrv_ivp_attach_string
    $   say ""
    $!
    $ldrv_ivp_get_reply:
    $   read /prompt="Are you satisfied with that? (Y/N): " sys$command
    ans
    $   say ""
    $   ans = f$extract(0,1,f$edit(ans, "upcase,collapse"))
    $   if .not.ans then goto ldrv_ivp_reset_attach_string
    $   !
    $   say ""
    $   @sys$library:sql$setver 6.0
    $   define/nolog/user sql$database "''ldrv_ivp_attach_string'"
    $   sql :== $sql$
    $   !
    $   sql
    set verify
    show tables
    exit
    $   say "IVP completed successfully."
    $   say ldrv_ivp_attach_string
    $   say ""
    $!
    $ldrv_ivp_get_reply:
    $   read /prompt="Are you satisfied with that? (Y/N): " sys$command
    ans
    $   say ""
    $   ans = f$extract(0,1,f$edit(ans, "upcase,collapse"))
    $   if .not.ans then goto ldrv_ivp_reset_attach_string
    $   !
    $   say ""
    $   @sys$library:sql$setver 6.0
    $   define/nolog/user sql$database "''ldrv_ivp_attach_string'"
    $   sql :== $sql$
    $   !
    $   sql
    set verify
    show tables
    exit
    $   say "IVP completed successfully."
    $   exit
    $!^L
    $!
    *****************************************************************************
    $setup_gateway_strings:
    $
    $!      Initialize common strings
    $!
    $!      Note: when we synchronize version numbering for all the gateways,
    $!      we can initialize gateway_version here instead of initializing
    $!      it separately for each gateway.
    $!
    $   arch = f$edit(f$getsyi("arch_name"),"upcase")
    $   if arch .eqs. "VAX"
    $   then
    $       operating_system = "OpenVMS VAX"
    $   else
    $       operating_system = "OpenVMS AXP"
    $   endif
    $
    $   ivp_filename = f$parse(f$environment("procedure"),,,"name")
    $   gateway_id = f$extract(0,4,ivp_filename)
    $
    $   if "''gateway_id'" .EQS. "LEDA"
    $   then
    $       gateway_full_name = "DEC DB Integrator Gateway for EDA/SQL"
    $       gateway_version   = "V3.1-00"
    $       gateway_example_attach = -
              "/TYPE=EDASQL/SERVER=mvspub/USER=vida2/PASSWORD=spring;"
    $       return
    $   endif
    $
    $   if "''gateway_id'" .EQS. "LSYB"
    $   then
    $       gateway_full_name = "DEC DB Integrator Gateway for SYBASE"
    $       gateway_version   = "V3.1-00"
    $       gateway_example_attach = -
    
    "/TYPE=SYBASE/SERVER=SYBASE/USER=fred/PASSWORD=chris/DATABASE=mydatabase;"
    $       return
    $   endif
    $
    $   if "''gateway_id'" .EQS. "LORA"
    $   then
    $       gateway_full_name = "DEC DB Integrator Gateway for ORACLE"
    $       gateway_version   = "V3.1-00"
    $       gateway_example_attach = -
    
    "/TYPE=ORACLE/USER=SCOTT/PASSWORD=TIGER/NODE=NODE1-V7P/TABLE=COLLEGES;"
    $       return
    $       return
    $   endif
    $
    $   if "''gateway_id'" .EQS. "LSQK"
    $   then
    $       gateway_full_name = "DEC DB Integrator Gateway for SequeLink"
    $       gateway_version   = "V3.1-00"
    $       gateway_example_attach = -
    
    "/TYPE=DB2/USER=FRED/PASSWORD=CHRIS/NODE=NODE01/TIDCS=DBIV/ACCESS_NAME=MYACCESS
    /
    LOGON_MODE=MYMODE/DATABASE=MYDATABASE;"
    $       return
    $   endif
    $
    $   if "''gateway_id'" .EQS. "LSQK"
    $   then
    $       gateway_full_name = "DEC DB Integrator Gateway for SequeLink"
    $       gateway_version   = "V3.1-00"
    $       gateway_example_attach = -
    
    "/TYPE=SQLNK/NODE=NODEQ/TRANSPORT_TYPE=TCP/SERVICE=Sqlnk_Informix/USER=fred/
    PASSWORD=chris/DATABASE=mydatabase;"
    $       return
    $   endif
    $
    $   say "Error in IVP: unrecognized gateway"
    $   goto ldrv_ivp_warning
    $!^L
    $!
    *******************************************************************************
    *
    $ldrv_ivp_interrupt:
    $   set noon
    $   say ""
    $   say "IVP cancelled via CTRL/Y."
    $   say ""
    $   say ""
    $   exit
    $!^L
    
    
    
    
    
    
    The IVP executed with VERIFY,
    
    $!
    --------------------------------------------------------------------------
    $!   c Digital Equipment Corporation 1993,1994. All rights reserved.
    $!
    $!   Restricted Rights: Use, duplication, or disclosure by the U.S.
    $!   Government is subject to restrictions as set forth in subparagraph
    $!   (c) (1) (ii) of DFARS 252.227-7013, or in FAR 52.227-19, or in FAR
    $!   52.227-14 Alt. III, as applicable.
    $!
    $!   This software is proprietary to and embodies the confidential
    $!   technology of Digital Equipment Corporation. Possession, use, or
    $!   copying of this software and media is authorized only pursuant to a
    $!   valid written license from Digital or an authorized sublicensor.
    $!
    --------------------------------------------------------------------------
    $!++
    $!  Facility:
    $!      LINK
    $!
    $!  Module:
    $!      LDRV$IVP.COM
    $!
    $!  Product:
    $!      LEDA031     (Product Name)
    $!      LSYB031     (Product Name)
    $!      LORA031     (Product Name)
    $!      LDB2030     (Product Name)
    $!      LSQK031     (Product Name)
    $!
    $!  Abstract:
    $!      This is an installation verification procedure (IVP). It checks
    the
    $!      installation of a DEC DB Integrator Gateway for EDA/SQL Sybase,
    Oracle,
    $!      DB2, and SequeLink.
    $!
    $!  Parameters:
    $!
    $!      None
    $!
    $!  Environment:
    $!      This file is expected to be named LEDA$IVP.COM, LSYB$IVP.COM,
    $!      LORA$IVP.COM, LDB2$IVP.COM, or LSQK$IVP.COM.
    $!      The routine setup_gateway_strings is dependent on the first 4
    $!      characters of the filename.
    $!
    $!++
    $   on warning   then goto ldrv_ivp_warning
    $   on control_y then goto ldrv_ivp_interrupt
    $   !
    $ say := "write sys$output"
    $
    $!
    $   gosub setup_gateway_strings
    $setup_gateway_strings:
    $
    $!      Initialize common strings
    $!
    $!      Note: when we synchronize version numbering for all the gateways,
    $!      we can initialize gateway_version here instead of initializing
    $!      it separately for each gateway.
    $!
    $   arch = f$edit(f$getsyi("arch_name"),"upcase")
    $   if arch .eqs. "VAX"
    $   else
    $       operating_system = "OpenVMS AXP"
    $   endif
    $
    $   ivp_filename = f$parse(f$environment("procedure"),,,"name")
    $   gateway_id = f$extract(0,4,ivp_filename)
    $
    $   if "LORA" .EQS. "LEDA"
    $   endif
    $
    $   if "LORA" .EQS. "LSYB"
    $   endif
    $
    $   if "LORA" .EQS. "LORA"
    $   then
    $       gateway_full_name = "DEC DB Integrator Gateway for ORACLE"
    $       gateway_version   = "V3.1-00"
    $       gateway_example_attach = -
    
    "/TYPE=ORACLE/USER=SCOTT/PASSWORD=TIGER/NODE=NODE1-V7P/TABLE=COLLEGES;"
    $       return
    $!
    $   say " "
    
    $   say "
    *****************************************************************"
        *****************************************************************
    $   say " "
    
    $   say "               Installation Verification Procedure (IVP) for
                   Installation Verification Procedure (IVP) for
    $   say "               DEC DB Integrator Gateway for ORACLE V3.1-00"
                   DEC DB Integrator Gateway for ORACLE V3.1-00
    $   say "                        for OpenVMS AXP
                            for OpenVMS AXP
    $   say " "
    
    $   say "    Copyright Digital Equipment Corporation 1993,1994. All
    rights reserved."
        Copyright Digital Equipment Corporation 1993,1994. All rights
    reserved.
    $   say " "
    
    $   say "    This IVP verifies that all the gateway images are in
    place and"
        This IVP verifies that all the gateway images are in place and
    $   say "    a simple query can be executed. "
        a simple query can be executed.
    $   say " "
    
    $   say "
    *****************************************************************"
        *****************************************************************
    $   say " "
    
    $   say ""
    
    $   say "Enter a SQL attach string terminated by a semi-colon."
    Enter a SQL attach string terminated by a semi-colon.
    $   say "Example:"
    Example:
    $   say
    "/TYPE=ORACLE/USER=SCOTT/PASSWORD=TIGER/NODE=NODE1-V7P/TABLE=COLLEGES;"
    /TYPE=ORACLE/USER=SCOTT/PASSWORD=TIGER/NODE=NODE1-V7P/TABLE=COLLEGES;
    $
    $   ! issue case-sensitive message if it's SYBASE
    $   if "LORA" .EQS. "LSYB"
    $   endif
    $!
    $ldrv_ivp_reset_attach_string:
    $   ldrv_ivp_attach_string =""
    $   ldrv_ivp_prompt = "attach string: "
    $!
    $ldrv_ivp_get_attach_string:
    $   read /prompt="attach string: " sys$command ldrv_ivp_attach
    attach string: attach 'filename/type=oracle/node=2:/user=gl/pass=gl';
    $   ldrv_ivp_prompt = "_: "
    $   ldrv_ivp_attach = f$edit(ldrv_ivp_attach, "trim")
    $   if f$extract(f$length(ldrv_ivp_attach)-1,1,
    ldrv_ivp_attach).eqs.";" then goto ldrv_ivp_got_attach_string
    $ldrv_ivp_got_attach_string:
    $   ldrv_ivp_attach_string =  ldrv_ivp_attach_string +
    f$extract(0,f$length(ldrv_ivp_attach)-1, ldrv_ivp_attach)
    $   say ""
    
    $   say "The current string is: "
    The current string is:
    $   say ldrv_ivp_attach_string
    attach 'filename/type=oracle/node=2:/user=gl/pass=gl'
    $   say ""
    
    $!
    $ldrv_ivp_get_reply:
    $   read /prompt="Are you satisfied with that? (Y/N): " sys$command
    ans
    Are you satisfied with that? (Y/N): y
    $   say ""
    
    $   ans = f$extract(0,1,f$edit(ans, "upcase,collapse"))
    $   if .not.ans then goto ldrv_ivp_reset_attach_string
    $   !
    $   say ""
    
    $   @sys$library:sql$setver 6.0
    $! Copyright c Oracle Corporation 1995.  All Rights Reserved.
    $!
    $!      File: SQL$SETVER.COM
    $!
    $! This command procedure sets up the necessary symbols and
    $! logical names needed to run a particular version of the Common Components
    $! (SQL or DISPATCH)
    $!
    $!      P1 = (REQUIRED)
    $!              version (ie: S for STANDARD 4.0, 4.1 for MULTIVERSION 4.1)
    $!              or RESET to reset SQL symbols
    $!              or REMOVE to remove SQL and DISPATCH logicals
    $!              or HIGHEST to set SQL and DISPATCH to the highest version
    $!
    $!      P2 = (OPTIONAL)
    $!              Logical name table switch (/PROCESS, /GROUP, /JOB, or /SYSTEM)
    $!              default is /PROCESS
    $!              or REMOTE to set only DISPATCH logicals for fast remote
    access
    $!
    $!      P3 = (OPTIONAL)
    $!              Date compatibility switch (see Release Notes for 4.1 for more
    $!              information. Options are DATE or NODATE with DATE as the
    $!              default. This can go in P2 if a logical name table switch
    $!              isn't used.
    $!
    $!      P4 = (OPTIONAL)
    $!              Common Component logicals to set  (SQL, DISPATCH, or ALL)
    $!              Default is ALL. This can go in P2 or P3 as the last
    $!              parameter.
    
    $!----------------------------------------------------------------------
    $!
    $       ON CONTROL_Y THEN GOTO SQL$_RESET
    $       ON WARNING THEN GOTO SQL$_WARNING
    $!
    $       RESET_FLAG = "FALSE"
    $       DELETE_FILE = "DELETE/NOCONFIRM/NOLOG"
    $       P1_COUNT = 0
    $!
    $       P1 = F$EDIT(P1,"UPCASE")
    $       P2 = F$EDIT(P2,"UPCASE")
    $       P3 = F$EDIT(P3,"UPCASE")
    $       P4 = F$EDIT(P4,"UPCASE")
    $!
    $       IF P1 .EQS. "RESET"
    $       ENDIF
    $!
    $       IF P1 .EQS. "HIGHEST"
    $       ENDIF
    $!
    $ ASK_P1:
    $!
    $       IF F$MODE() .EQS. "BATCH"
    $       ELSE
    $           IF "6.0" .EQS. "" THEN INQUIRE P1 -
                    "Enter MULTIVERSION version number (n.n) or S (for STANDARD) "
    $           IF "6.0" .EQS. ""
    $           ENDIF
    $       ENDIF
    $!
    $       IF "6.0" .NES. "REMOVE"
    $       THEN
    $           IF "6.0" .EQS. "S"
    $           ELSE
    $               IF F$LOCATE(".",P1) .EQ. F$LENGTH(P1) THEN -
                        P1 = F$EXTRACT(0,1,P1) + "." + F$EXTRACT(1,1,P1)
    $               MAJ_VER = "6"
    $               MIN_VER = "0"
    $               VERSION := 6.0
    $               VARIANT := 60
    $               IF (F$TYPE (MAJ_VER) .NES. "INTEGER" .OR. -
                        F$TYPE (MIN_VER) .NES. "INTEGER") .OR. -
                       (F$LEN(VERSION) .NES. F$LEN(P1) .AND. -
                        F$LEN(VERSION)+1 .NES. F$LEN(P1))
    $               ENDIF
    $           ENDIF
    $       ENDIF
    $       !
    $       ! Check the remaining parameters and set up correctly
    $       !
    $       ! Check for remote request for only DISPATCH logicals. This
    prevents
    $       ! a decnet timeout.
    $       !
    $       IF P2 .EQS. "REMOTE"
    $       ENDIF
    $!
    $       IF (P2 .EQS. "SQL") .OR. (P2 .EQS. "DISPATCH") .OR. (P2 .EQS. "ALL")
    $       ELSE
    $           IF (P2 .EQS. "DATE") .OR. (P2 .EQS. "NODATE")
    $           ELSE
    $               IF (P3 .EQS. "SQL") .OR. (P3 .EQS. "DISPATCH") -
                        .OR. (P3 .EQS. "ALL")
    $               ENDIF
    $           ENDIF
    $       ENDIF
    $!
    $       GOSUB VALIDATE_PARAMETERS
    $ VALIDATE_PARAMETERS:
    $       !
    $       ! Validate all parameters. Print error message and exit when a problem
    $       ! occurs.
    $       !
    $       IF P2 .EQS. ""
    $       THEN
    $           P2 = "/PROCESS"
    $       ELSE
    $       ENDIF
    $!
    $       IF P2 .EQS. "/SYSTEM/EXEC" .AND. F$PRIVILEGE("SYSNAM") .EQS. "FALSE"
    $       ENDIF
    $!
    $       IF P2 .EQS. "/GROUP" .AND. F$PRIVILEGE("SYSPRV") .EQS. "FALSE" 
    .AND. -
                F$PRIVILEGE("GRPNAM") .EQS. "FALSE"
    $       ENDIF
    $!
    $       VALID_P3 = ",DATE,NODATE,SQL,DISPATCH,ALL,NOSYSTEM,"
    $       IF P3 .EQS. "" THEN P3 = "DATE"
    $       IF F$LOCATE(",DATE,",VALID_P3) .EQ. F$LENGTH(VALID_P3)
    $       ENDIF
    $!
    $       IF P4 .EQS. "" THEN P4 = "ALL"
    $       IF (P4 .NES. "SQL") .AND. (P4 .NES. "DISPATCH") -
            .AND. (P4 .NES. "ALL")
    $       ENDIF
    $
    $ RETURN
    $       LNM_TBL = "LNM$"+F$EXTRACT(1,40,P2)
    $!
    $       SQL$$PARAM == P4
    $       !
    $       ! Save the current environment
    $       !
    $       SET NOON
    $!
    $       CUR_RDBSERVER           = F$TRNLNM("RDBSERVER",LNM_TBL)
    $       CUR_RDB$DISPATCH_IDENT  =
    F$TRNLNM("RDB$DISPATCH_IDENT",LNM_TBL)
    $       CUR_RDB$DISPATCH_VERSION_VARIANT -
                                =
    F$TRNLNM("RDB$DISPATCH_VERSION_VARIANT",LNM_TBL)
    $       CUR_SQL$IDENT           = F$TRNLNM("SQL$IDENT",LNM_TBL)
    $       CUR_SQL$VERSION_VARIANT =
    F$TRNLNM("SQL$VERSION_VARIANT",LNM_TBL)
    $       CUR_SQLSAMPLE           = F$TRNLNM("SQL$SAMPLE",LNM_TBL)
    $       CUR_SQL                 = F$TRNLNM("SQL$",LNM_TBL)
    $       CUR_SQLPRE              = F$TRNLNM("SQL$PRE",LNM_TBL)
    $       CUR_SQLMOD              = F$TRNLNM("SQL$MOD",LNM_TBL)
    $       CUR_SQL$USER            = F$TRNLNM("SQL$USER",LNM_TBL)
    $       CUR_SQL$MSG             = F$TRNLNM("SQL$MSG",LNM_TBL)
    $       CUR_SQL$SHR             = F$TRNLNM("SQL$SHR",LNM_TBL)
    $       CUR_SQL$HELP_OLD        = F$TRNLNM("SQL$HELP_OLD",LNM_TBL)
    $!
    $       SET ON
    $!      RESET_FLAG = "TRUE"
    $!
    $       IF P1 .EQS. "REMOVE" THEN GOTO REMOVE_LOGICALS
    $       !
    $       ! Check for existance of requested version
    $       !
    $       IF (P4 .EQS. "SQL")
    $       ENDIF
    $!
    $       IF (P4 .EQS. "DISPATCH")
    $       ENDIF
    $!
    $       IF (P4 .EQS. "ALL")
    $       THEN
    $           COMMON_COMP = "SQL"
    $           FILE = "SYS$COMMON:[SYSLIB]SQL$SHR60.EXE"
    $           FILE2 = "SYS$COMMON:[SYSLIB]RDB$SHARE60.EXE"
    $       ENDIF
    $!
    $       IF F$SEARCH(FILE) .EQS. ""
    $       THEN
    $           IF P1 .EQS. "S"
    $           ELSE
    $               FILE ="SYS$COMMON:[SYSLIB]SQL$SHR.EXE"
    $               FILE2 ="SYS$COMMON:[SYSLIB]RDB$SHARE.EXE"
    $               IF F$SEARCH(FILE) .EQS. ""
    $               ELSE
    $!                  If the requested multiversion is not found, but a standard
    $!                  version is found, set the variant to blank.
    $                   VARIANT = ""
    $               ENDIF
    $           ENDIF
    $       ENDIF
    $       !
    $       ! Get the IMAGE VERSIONS to set up the different sample directories
    $       ! and the NODATE images for V4.1, and to set up logicals for shover.
    $       !
    $       IF P4 .EQS. "SQL"
    $       ENDIF
    $!
    $       IF P4 .EQS. "DISPATCH"
    $       ENDIF
    $!
    $       IF P4 .EQS. "ALL"
    $       THEN
    $           CALL EXTRACT_VERSION "SYS$COMMON:[SYSLIB]SQL$SHR.EXE;0"
    $ EXTRACT_VERSION: SUBROUTINE
    $!
    $! (IN) P1 = image file name
    $! (OUT) SQL$$EXTRACTED_VERSION = version in image ident
    $!
    $       ON WARNING THEN CALL  WARNING_EXIT_HANDLER
    $       ON CONTROL_Y THEN CALL CONTROL_Y_EXIT_HANDLER
    $       SET NOON
    $       IF F$TRNLNM("SYS$SCRATCH") .EQS. ""
    $       ELSE
    $           DEFINE/USER SYS$OUTPUT NL:
    $           DEFINE/USER SYS$ERROR NL:
    $           DIR SYS$SCRATCH:DECRDB$*.TMP
    $           IF $SEVERITY .EQ. 2 .OR. $SEVERITY .EQ. 4
    $           ENDIF
    $       ENDIF
    $       TMP_FILE = "SYS$SCRATCH:SQL$" + F$GETJPI("","PID") + "VER.TMP"
    $       TMP_FILE2 = TMP_FILE + "2"
    $       DEFINE/USER SYS$ERROR _NL:
    $       DEFINE/USER SYS$OUTPUT _NL:
    $       ANALYZE/IMAGE/HEAD
    SYS$COMMON:[SYSLIB]SQL$SHR.EXE;0/OUT=SYS$SCRATCH:SQL$684051C4VER.TMP
    $       SEARCH/WINDOW=1 SYS$SCRATCH:SQL$684051C4VER.TMP "IMAGE FILE
    IDENT"/OUT=SYS$SCRATCH:SQL$684051C4VER.TMP2
    $       OPEN/READ SQL$$FILE1 SYS$SCRATCH:SQL$684051C4VER.TMP2
    $       READ SQL$$FILE1 REC1
    $       CLOSE SQL$$FILE1
    $       SET PROT=O:RWED
    SYS$SCRATCH:SQL$684051C4VER.TMP;*,SYS$SCRATCH:SQL$684051C4VER.TMP2;*
    $       CALL DELETE_FILE SYS$SCRATCH:SQL$684051C4VER.TMP;*
    $ DELETE_FILE: SUBROUTINE
    $ ! (IN ) P1 = filename
    $       IF F$SEARCH(P1) .NES. ""
    $       THEN
    $           DELETE_FILE SYS$SCRATCH:SQL$684051C4VER.TMP;*
    $           TMP = F$SEARCH("") !force search to clear its context buffer
    $       ENDIF
    $ ENDSUBROUTINE
    $       CALL DELETE_FILE SYS$SCRATCH:SQL$684051C4VER.TMP2;*
    $ DELETE_FILE: SUBROUTINE
    $ ! (IN ) P1 = filename
    $       IF F$SEARCH(P1) .NES. ""
    $       THEN
    $           DELETE_FILE SYS$SCRATCH:SQL$684051C4VER.TMP2;*
    $           TMP = F$SEARCH("") !force search to clear its context buffer
    $       ENDIF
    $ ENDSUBROUTINE
    $       SET ON
    $       !
    $       ! format of output of the search should be 1 line and look
    $       ! something like :
    $       !      " image file identification: "<name><versiontype>n.n-0""
    $       ! note the following extraction will work as long as
    $       !  1/.      the only period is in the version number
    $       !  2/.      the major id is less than 10 ( ie. one digit )
    $       !
    $       PERIOD_LOC = F$LOCATE(".",REC1)
    $       NUM = F$EXTRACT(PERIOD_LOC-2,F$LENGTH(REC1),REC1)
    $       DASH_LOC = F$LOCATE("-",NUM)
    $       QUOTE_LOC= F$LOCATE("""",NUM)
    $       SQL$$EXTRACTED_VERSION == F$EXTRACT(1,DASH_LOC-1,NUM)
    $       SQL$$EXTRACTED_VERSION == F$EXTRACT(0,3,SQL$$EXTRACTED_VERSION)
    $       SQL$$IDENT == F$EXTRACT(0,QUOTE_LOC,NUM)
    $ ENDSUBROUTINE
    $           SQL$_VERSION = SQL$$EXTRACTED_VERSION
    $           SQL$_IDENT = SQL$$IDENT
    $           GOSUB VALIDATE_IDENT
    $ VALIDATE_IDENT:
    $       !
    $       ! Validate that the image ident matches the image name for
    $       ! Multiversion image.
    $       !
    $       IF (P1 .NES. "S") .AND. (P1 .NES. "")
    $       THEN
    $           IF "6.0" .NES. "6.1"
    $           THEN
    $               WRITE SYS$OUTPUT " "
    
    $               WRITE SYS$OUTPUT "%SQL-E-SETVER
    SYS$COMMON:[SYSLIB]SQL$SHR.EXE
    Image Ident Problem"
    %SQL-E-SETVER SYS$COMMON:[SYSLIB]SQL$SHR.EXE Image Ident Problem
    $               WRITE SYS$OUTPUT "%SQL-E-SETVER IMAGE IDENT = " + -
                        "6.1, VERSION = 6.0"
    %SQL-E-SETVER IMAGE IDENT = 6.1, VERSION = 6.0
    $               WRITE SYS$OUTPUT " "
    
    $               CALL CLEANUP_RTN
    $ CLEANUP_RTN: SUBROUTINE
    $       ON WARNING THEN CONTINUE
    $       ON CONTROL_Y THEN CONTINUE
    $       ! Close the temp file if its open
    $       IF F$TRNLNM("SQL$$FILE1") .NES. "" THEN CLOSE SQL$$FILE1
    $       ! Cleanup any global symbols this routine may have used
    $       CALL DELETE_SYMBOL SQL$$EXTRACTED_VERSION
    $ DELETE_SYMBOL: SUBROUTINE
    $ ! (IN ) P1 = symbol
    $       SET NOON
    $       DEFINE/USER SYS$ERROR _NL:
    $       DEFINE/USER SYS$OUTPUT _NL:
    $       DELETE/SYMBOL/GLOBAL SQL$$EXTRACTED_VERSION
    $       SET ON
    $ ENDSUBROUTINE
    $       CALL DELETE_SYMBOL SQL$$IDENT
    $ DELETE_SYMBOL: SUBROUTINE
    $ ! (IN ) P1 = symbol
    $       SET NOON
    $       DEFINE/USER SYS$ERROR _NL:
    $       DEFINE/USER SYS$OUTPUT _NL:
    $       DELETE/SYMBOL/GLOBAL SQL$$IDENT
    $       SET ON
    $ ENDSUBROUTINE
    $       CALL DELETE_SYMBOL SQL$$PARAM
    $ DELETE_SYMBOL: SUBROUTINE
    $ ! (IN ) P1 = symbol
    $       SET NOON
    $       DEFINE/USER SYS$ERROR _NL:
    $       DEFINE/USER SYS$OUTPUT _NL:
    $       DELETE/SYMBOL/GLOBAL SQL$$PARAM
    $       SET ON
    $ ENDSUBROUTINE
    $       IF "" .EQS. "TRUE" THEN DEASSIGN SYS$SCRATCH
    $       CALL DELETE_SYMBOL DECRDB$$SYS$SCRATCH
    $ DELETE_SYMBOL: SUBROUTINE
    $ ! (IN ) P1 = symbol
    $       SET NOON
    $       DEFINE/USER SYS$ERROR _NL:
    $       DEFINE/USER SYS$OUTPUT _NL:
    $       DELETE/SYMBOL/GLOBAL DECRDB$$SYS$SCRATCH
    $       SET ON
    $ ENDSUBROUTINE
    $ ENDSUBROUTINE
    $               EXIT %X10000000
    $ldrv_ivp_warning:
    $   _status = $status
    $   set noon
    $   say ""
    
    $   say "Some error ocurred in IVP."
    Some error ocurred in IVP.
    $   say ""
    
    $   exit $status
    
    
    
    
    
    
                                                                          
    
    
    
    
    
                                                                       
T.RTitleUserPersonal
Name
DateLines
1050.1Change sql$setver 6.0 to sql$setver 6.1ORAREP::NECSC::BASTINEBring on the next season!!Tue Apr 23 1996 08:4622
>    %SQL-E-SETVER SYS$COMMON:[SYSLIB]SQL$SHR.EXE Image Ident Problem
>    %SQL-E-SETVER IMAGE IDENT = 6.1, VERSION = 6.0
    
The problem is this line in the IVP command file:


    $   @sys$library:sql$setver 6.0


>    He is running an ALPHA with VMS V6.2 and DBI GW V3.1 for ORACLE
>    			And RDB V6.1
    

If he is running RDB 6.1, then have him change the above line in the IVP
command file to this:

$   @sys$library:sql$setver 6.1

and the problem will go away.

Renee Bastine
DBI support
1050.2highest set sql to highest availableBROKE::ABUGOVTue Apr 23 1996 10:118
    
    Actually, as of 6.1 sql$setver will take as a parameter the word
    "highest" so that it will set up to the highest version available.
    This customer might want to change it to highest as opposed to
    hard-coding a number in there (highest was added specifically to help
    us get around this problem).
    
    dan