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

A76940-01

Library

Product

Contents

Index

Prev Up Next

Internal Persistent LOBs, 20 of 42


Read a Portion of the LOB (substr)

Figure 9-23 Use Case Diagram: Read a Portion of the LOB (substr)


See:

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

Purpose

This procedure describes how to read portion of the LOB (substring).

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

This example demonstrates reading a portion from sound-effect Sound.

Examples

Examples are provided in the following programmatic environments:

PL/SQL (DBMS_LOB Package): Read a Portion of the LOB (substr)

/* Note that the example procedure substringLOB_proc is not part of the 
   DBMS_LOB package: */
CREATE OR REPLACE PROCEDURE substringLOB_proc IS
    Lob_loc           BLOB;
    Amount            BINARY_INTEGER := 32767;
    Position          INTEGER := 1024;
    Buffer            RAW(32767);
BEGIN
    /* Select the LOB: */
    SELECT Sound INTO Lob_loc FROM Multimedia_tab
       WHERE Clip_ID = 1;
    /* Opening the LOB is optional: */
    DBMS_LOB.OPEN (Lob_loc, DBMS_LOB.LOB_READONLY);
    Buffer := DBMS_LOB.SUBSTR(Lob_loc, Amount, Position);
    /* Process the data */
    /* Closing the LOB is mandatory if you have opened it: */
    DBMS_LOB.CLOSE (Lob_loc);
END;

/* In the following SQL statement, 255 is the amount to read 
   and 1 is the starting offset from which to read: */
SELECT DBMS_LOB.SUBSTR(Sound, 255, 1) FROM Multimedia_tab WHERE Clip_ID = 1;

COBOL (Pro*COBOL): Read a Portion of the LOB (substr)

       IDENTIFICATION DIVISION.
       PROGRAM-ID. BLOB-SUBSTR.
       ENVIRONMENT DIVISION.
       DATA DIVISION.
       WORKING-STORAGE SECTION.

       01  BLOB1          SQL-BLOB.
       01  BUFFER2        PIC X(32767) VARYING.
       01  AMT            PIC S9(9) COMP.
       01  POS            PIC S9(9) COMP VALUE 1.
       01  USERID   PIC X(11) VALUES "SAMP/SAMP".
           EXEC SQL INCLUDE SQLCA END-EXEC.
           EXEC SQL VAR BUFFER2 IS VARRAW(32767) END-EXEC.

       PROCEDURE DIVISION.
       BLOB-SUBSTR.
           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 :BLOB1 END-EXEC.
 
           EXEC SQL WHENEVER NOT FOUND GOTO END-OF-BLOB END-EXEC.
             EXEC SQL 
              SELECT FRAME INTO :BLOB1
              FROM MULTIMEDIA_TAB M WHERE M.CLIP_ID = 1 END-EXEC.
           DISPLAY "Selected the BLOB".

      * Open the BLOB for READ ONLY: 
           EXEC SQL LOB OPEN :BLOB1 READ ONLY END-EXEC.

      * Execute PL/SQL to get SUBSTR functionality: 
           MOVE 5 TO AMT.
           EXEC SQL EXECUTE
             BEGIN 
               :BUFFER2 := DBMS_LOB.SUBSTR(:BLOB1,:AMT,:POS); END; END-EXEC.
           EXEC SQL LOB CLOSE :BLOB1 END-EXEC.
           DISPLAY "Substr: ", BUFFER2-ARR(POS:AMT).

       END-OF-BLOB.
           EXEC SQL WHENEVER NOT FOUND CONTINUE END-EXEC.
           EXEC SQL FREE :BLOB1 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++): Read a Portion of the LOB (substr)

/* Pro*C/C++ lacks an equivalent embedded SQL form for the DBMS_LOB.SUBSTR()
   function.  However, Pro*C/C++ can interoperate with PL/SQL using anonymous
   PL/SQL blocks embedded in a Pro*C/C++ program as this example shows: */

#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);
}

#define BufferLength 32767

void substringLOB_proc()
{
  OCIBlobLocator *Lob_loc;
  int Position = 1;
  int Amount = BufferLength;
  struct {
    unsigned short Length;
    char Data[BufferLength];
  } Buffer;
  /* Datatype equivalencing is mandatory for this datatype: */
  EXEC SQL VAR Buffer IS VARRAW(BufferLength);

  EXEC SQL WHENEVER SQLERROR DO Sample_Error();
  EXEC SQL ALLOCATE :Lob_loc;
  EXEC SQL SELECT Sound INTO Lob_loc
           FROM Multimedia_tab WHERE Clip_ID = 1;
  /* Open the BLOB: */
  EXEC SQL LOB OPEN :Lob_loc READ ONLY;
  /* Invoke SUBSTR() from within an anonymous PL/SQL block: */
  EXEC SQL EXECUTE
    BEGIN
      :Buffer := DBMS_LOB.SUBSTR(:Lob_loc, :Amount, :Position);
    END;
  END-EXEC;
  /* Close the BLOB: */
  EXEC SQL LOB CLOSE :Lob_loc;
  /* Process the Data */
  /* Release resources used by the locator: */
  EXEC SQL FREE :Lob_loc;
}

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

Visual Basic (OO4O): Read a Portion of the LOB (substr)

'Note that reading a portion of a LOB (or BFILE) in OO4O is accomplished by 
'setting the OraBlob.Offset and OraBlob.chunksize properties.
'Using OraClob.Read mechanism
Dim MySession As OraSession
Dim OraDb As OraDatabase
Dim OraDyn as OraDynaset, OraStory as OraClob, amount_read%, chunksize%, chunk

Set MySession = CreateObject("OracleInProcServer.XOraSession")
Set OraDb = MySession.OpenDatabase("exampledb", "samp/samp", 0&)

Set OraDyn = OraDb.CreateDynaset("SELECT * FROM Multimedia_tab", ORADYN_DEFAULT)
Set OraStory = OraDyn.Fields("Story").Value

'Let's read 100 bytes from the 500th byte onwards: 
OraStory.Offset = 500
OraStory.PollingAmount = OraStory.Size 'Read entire CLOB contents
amount_read = OraStory.Read(chunk, 100) 
'chunk returned is a variant of type byte array

Java (JDBC): Read a Portion of the LOB (substr)

import java.io.InputStream;
import java.io.OutputStream;

// Core JDBC classes: 
import java.sql.DriverManager;
import java.sql.Connection;
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_79
{

  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
    {
       BLOB lob_loc = null;
       byte buf[] = new byte[MAXBUFSIZE];

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

       OracleCallableStatement cstmt = (OracleCallableStatement)
          conn.prepareCall ("BEGIN DBMS_LOB.OPEN(?, "
                            +"DBMS_LOB.LOB_READONLY); END;");
       cstmt.setBLOB(1, lob_loc);
       cstmt.execute();

       // MAXBUFSIZE is the number of bytes to read and 1000 is the offset from  
       // which to start reading: 
       buf = lob_loc.getBytes(1000, MAXBUFSIZE);
      // Display the contents of the buffer here.
   
      cstmt = (OracleCallableStatement) 
         conn.prepareCall ("BEGIN DBMS_LOB.CLOSE(?); END;");
      cstmt.setBLOB(1, lob_loc);
      cstmt.execute();

      stmt.close();
      cstmt.close();
     conn.commit();
     conn.close();
    }
    catch (SQLException e)
    {
       e.printStackTrace();
    }
  }
}


Prev Up Next
Oracle
Copyright © 1999 Oracle Corporation.

All Rights Reserved.

Library

Product

Contents

Index