Oracle8i Application Developer's Guide - Large Objects (LOBs)
Release 2 (8.1.6)

Part Number A76940-01

Library

Product

Contents

Index

Go to previous page Go to beginning of chapter Go to next page

Internal Persistent LOBs, 22 of 42


See If a Pattern Exists in the LOB (instr)

Figure 9-25 Use Case Diagram: See If a Pattern Exists in the LOB (instr)


See:

"Use Case Model: Internal Persistent LOBs Basic Operations", for all basic operations of Internal Persistent LOBs. 

Purpose

This procedure describes how to see if a pattern exists in the LOB (instr).

Usage Notes

Not applicable.

Syntax

See Chapter 3, "LOB Programmatic Environments" for a list of available functions in each programmatic environment. Use the following syntax references for each programmatic environment:

Scenario

The examples examine the storyboard text to see if the string "children" is present.

Examples

Examples are provided in the following programmatic environments:

PL/SQL (DBMS_LOB Package): See If a Pattern Exists in the LOB (instr)

/* Note that the example procedure instringLOB_proc is not part of the 
   DBMS_LOB package: */
CREATE OR REPLACE PROCEDURE instringLOB_proc IS
   Lob_loc        CLOB;
   Pattern        VARCHAR2(30) := 'children';
   Position       INTEGER := 0;
   Offset         INTEGER := 1;
   Occurrence     INTEGER := 1;
BEGIN
   /* Select the LOB: */
   SELECT Story INTO Lob_loc
      FROM Multimedia_tab
         WHERE Clip_ID = 1;
   /* Opening the LOB is optional: */
   DBMS_LOB.OPEN (Lob_loc, DBMS_LOB.LOB_READONLY);
   /* Seek for the pattern: */
   Position := DBMS_LOB.INSTR(Lob_loc, Pattern, Offset, Occurrence);
   IF Position = 0 THEN
      DBMS_OUTPUT.PUT_LINE('Pattern not found');
   ELSE
      DBMS_OUTPUT.PUT_LINE('The pattern occurs at '|| position);
   END IF;
   /* Closing the LOB is mandatory if you have opened it: */
   DBMS_LOB.CLOSE (Lob_loc);
END;

COBOL (Pro*COBOL): See If a Pattern Exists in the LOB (instr)

       IDENTIFICATION DIVISION.
       PROGRAM-ID. CLOB-INSTR.
       ENVIRONMENT DIVISION.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01  CLOB1          SQL-CLOB.
       01  PATTERN        PIC X(8) VALUE "children".
       01  POS            PIC S9(9) COMP.
       01  OFFSET         PIC S9(9) COMP VALUE 1.
       01  OCCURRENCE     PIC S9(9) COMP VALUE 1.
       01  USERID   PIC X(11) VALUES "SAMP/SAMP".
           EXEC SQL INCLUDE SQLCA END-EXEC.

       PROCEDURE DIVISION.
       CLOB-INSTR.
           EXEC SQL WHENEVER SQLERROR DO PERFORM SQL-ERROR END-EXEC.
           EXEC SQL
                CONNECT :USERID
           END-EXEC.

      * Allocate and initialize the CLOB locator: 
           EXEC SQL ALLOCATE :CLOB1 END-EXEC.
            EXEC SQL WHENEVER NOT FOUND GOTO END-OF-CLOB END-EXEC.
             EXEC SQL SELECT STORY INTO :CLOB1
                FROM MULTIMEDIA_TAB WHERE CLIP_ID = 1 END-EXEC.
 
      * Open the CLOB for READ ONLY: 
           EXEC SQL LOB OPEN :CLOB1 READ ONLY END-EXEC.

      * Execute PL/SQL to get INSTR functionality:
           EXEC SQL EXECUTE
             BEGIN 
               :POS := DBMS_LOB.INSTR(:CLOB1, :PATTERN,:OFFSET,:OCCURRENCE);
               END; END-EXEC.
           
           IF POS = 0
      *        Logic for pattern not found here
               DISPLAY "Pattern not found."
           ELSE
      *        Pos contains position where pattern is found
               DISPLAY "Pattern found."
           END-IF.
           EXEC SQL LOB CLOSE :CLOB1 END-EXEC.

       END-OF-CLOB.
           EXEC SQL WHENEVER NOT FOUND CONTINUE END-EXEC.
           EXEC SQL FREE :CLOB1 END-EXEC.
           EXEC SQL ROLLBACK WORK RELEASE END-EXEC.
           STOP RUN.

       SQL-ERROR.
           EXEC SQL WHENEVER SQLERROR CONTINUE END-EXEC.
           DISPLAY " ".
           DISPLAY "ORACLE ERROR DETECTED:".
           DISPLAY " ".
           DISPLAY SQLERRMC.
           EXEC SQL ROLLBACK WORK RELEASE END-EXEC.
           STOP RUN.

C/C++ (Pro*C/C++): See If a Pattern Exists in the LOB (instr)

#include <oci.h>
#include <stdio.h>
#include <sqlca.h>

void Sample_Error()
{
  EXEC SQL WHENEVER SQLERROR CONTINUE;
  printf("%.*s\n", sqlca.sqlerrm.sqlerrml, sqlca.sqlerrm.sqlerrmc);
  EXEC SQL ROLLBACK WORK RELEASE;
  exit(1);
}

void instringLOB_proc()
{
  OCIClobLocator *Lob_loc;
  char *Pattern = "The End";
  int Position = 0;
  int Offset = 1;
  int Occurrence = 1;

  EXEC SQL WHENEVER SQLERROR DO Sample_Error();
  EXEC SQL ALLOCATE :Lob_loc;
  EXEC SQL SELECT Story INTO :Lob_loc
           FROM Multimedia_tab WHERE Clip_ID = 1;
  /* Opening the LOB is Optional: */
  EXEC SQL LOB OPEN :Lob_loc;
  /* Seek the Pattern using DBMS_LOB.INSTR() in a PL/SQL block: */
  EXEC SQL EXECUTE
    BEGIN
      :Position := DBMS_LOB.INSTR(:Lob_loc, :Pattern, :Offset, :Occurrence);
    END;
  END-EXEC;
  if (0 == Position)
    printf("Pattern not found\n");
  else
    printf("The pattern occurs at %d\n", Position);
  /* Closing the LOB is mandatory if you have opened it: */
  EXEC SQL LOB CLOSE :Lob_loc;
  EXEC SQL FREE :Lob_loc;
}

void main()
{
  char *samp = "samp/samp";
  EXEC SQL CONNECT :samp;
  instringLOB_proc();
  EXEC SQL ROLLBACK WORK RELEASE;
}
 

Java (JDBC): See If a Pattern Exists in the LOB (instr)

import java.io.OutputStream;

// Core JDBC classes: 
import java.sql.DriverManager;
import java.sql.Connection;
import java.sql.Types;
import java.sql.Statement;
import java.sql.PreparedStatement;
import java.sql.ResultSet;
import java.sql.SQLException;

// Oracle Specific JDBC classes: 
import oracle.sql.*;
import oracle.jdbc.driver.*;

public class Ex2_91
{
  static final int MAXBUFSIZE = 32767;
  public static void main (String args [])
       throws Exception
  {
    // Load the Oracle JDBC driver: 
    DriverManager.registerDriver(new oracle.jdbc.driver.OracleDriver());

    // Connect to the database: 
    Connection conn =
      DriverManager.getConnection ("jdbc:oracle:oci8:@", "samp", "samp");

    // It's faster when auto commit is off: 
    conn.setAutoCommit (false);

    // Create a Statement: 
    Statement stmt = conn.createStatement ();
    try
    {
     final int offset = 1;       // Start looking at the first byte
     final int occurrence = 1;  // Start at the 1st occurrence of the pattern 
within the CLOB

   CLOB lob_loc = null;
   String pattern = new String("Junk"); // Pattern to look for within the CLOB.

       ResultSet rset = stmt.executeQuery (
          "SELECT story FROM multimedia_tab WHERE clip_id = 2");
   if (rset.next())
   {
     lob_loc = ((OracleResultSet)rset).getCLOB (1);
   }

   // Search for location of pattern string in the CLOB, starting at offset 1: 
   long result = lob_loc.position(pattern, offset);
   System.out.println("Results of Pattern Comparison : " + 
      Long.toString(result));

   stmt.close();
   conn.commit();
   conn.close();

    }
    catch (SQLException e)
    {
       e.printStackTrace();
    }
  }
}


Go to previous page Go to beginning of chapter Go to next page
Oracle
Copyright © 1996-2000, Oracle Corporation.

All Rights Reserved.

Library

Product

Contents

Index