Results 1 to 9 of 9

Thread: VB6/VBA Creating Access Database via Code

  1. #1

    Thread Starter
    Discovering Life Siddharth Rout's Avatar
    Join Date
    Feb 2005
    Location
    Mumbai, India
    Posts
    12,001

    VB6/VBA Creating Access Database via Code

    Inspired by this thread, I finally decided to put together a seperate thread on this.

    You can create an MDB Access database either with DAO or ADO. DAO is almost obselete now but some people still use it so I am including both the codes.

    ADO

    Set Reference to the following
    Microsoft ActiveX Data Objects x.xx Library
    Microsoft ADO Ext. x.xx for DDL and Security


    vb Code:
    1. Sub ADOSample()
    2.     Dim adoCat As ADOX.Catalog, adoTable As ADOX.Table
    3.     Dim tblCollection As Collection
    4.     Dim Filenm As String, strConn As String
    5.    
    6.     '~~> MDB to be created. Change this to relevant path and filename
    7.     Filenm = "C:\Temp\MyDatabase.mdb"
    8.    
    9.     '~~> Creating an instance of the ADOX-object.
    10.     Set adoCat = New ADOX.Catalog
    11.     '~~> Creating an instance of Collection-object.
    12.     Set tblCollection = New Collection
    13.     Set adoTable = New ADOX.Table
    14.    
    15.     strConn = "Provider=Microsoft.Jet.OLEDB.4.0;" & _
    16.               "Data Source=" & Filenm & ";"
    17.    
    18.     '~~> Deleting the existing copy of the database, if any.
    19.     On Error Resume Next
    20.     Kill Filenm
    21.     On Error GoTo 0
    22.      
    23.     '~~> Create the MDB.
    24.     adoCat.Create (strConn)
    25.    
    26.     '~~> Replace "Table1" with a name you like for your table
    27.     tblCollection.Add "Table1"
    28.      
    29.     With adoTable
    30.         '~~> Name the table.
    31.         .Name = "Table1"
    32.         '~~> Creating a field which also is the Primary Key
    33.         .Columns.Append "ID", adInteger
    34.         '~~> Set the Parent Catalog.
    35.         .ParentCatalog = adoCat
    36.         .Columns("ID").Properties("AutoIncrement").Value = True
    37.         '~~> Append the PrimaryKey
    38.         .Keys.Append "PrimaryKey", adKeyPrimary, "ID"
    39.                
    40.         '~~> Add rest of the fields... I have taken 4 types
    41.         .Columns.Append "intField1", adInteger  '~~ number
    42.         .Columns.Append "numField2", adNumeric  '~~ number, decimal
    43.         .Columns("numField2").Precision = 2
    44.         .Columns.Append "dateFiled3", adDate    '~~ Date
    45.         .Columns.Append "txtFiled4", adWChar    '~~ text
    46.     End With
    47.    
    48.     '~~> Finally add the Table to the MDB.
    49.     adoCat.Tables.Append adoTable
    50.    
    51.     '~~> Release the objects from the memory.
    52.     Set adoTable = Nothing
    53.     Set tblCollection = Nothing
    54.     Set adoCat = Nothing
    55.      
    56.     '~~> Inform user.
    57.     MsgBox "New .MDB Created - '" & Filenm & "'", vbInformation
    58. End Sub

    DAO

    Set reference to Microsoft DAO x.x Object Library

    vb Code:
    1. Sub DAOExample()
    2.     Dim tdefMDB As TableDef, txtFieldone As Field
    3.     Dim dateFieldone As Field, memoFieldone As Field, dbDatabase As Database
    4.     Dim sNewDBPathAndName As String
    5.    
    6.     '~~> MDB to be created. Change this to relevant path and filename
    7.     sNewDBPathAndName = "C:\Temp\MyDatabase.mdb"
    8.     Set dbDatabase = CreateDatabase(sNewDBPathAndName, dbLangGeneral, dbEncrypt)
    9.  
    10.     '~~> Create new TableDef (I am creating a table Table1)
    11.     Set tdefMDB = dbDatabase.CreateTableDef("Table1")
    12.  
    13.     '~~> Add fields to MDB
    14.     '~~> for eample I am creating One text field, 1 date field and
    15.     '~~> 1 memo field. Amend as applicable
    16.     Set txtFieldone = tdefMDB.CreateField("txtField1", dbText, 20)
    17.     Set dateFieldone = tdefMDB.CreateField("dateField1", dbDate)
    18.     Set memoFieldone = tdefMDB.CreateField("memoField1", dbMemo)
    19.    
    20.     '~~> Append the field objects to the TableDef
    21.     tdefMDB.Fields.Append txtFieldone
    22.     tdefMDB.Fields.Append dateFieldone
    23.     tdefMDB.Fields.Append memoFieldone
    24.  
    25.     '~~> Save TableDef definition by appending it to TableDefs collection.
    26.     dbDatabase.TableDefs.Append tdefMDB
    27.    
    28.     '~~> Inform user.
    29.     MsgBox "New .MDB Created - '" & sNewDBPathAndName & "'", vbInformation
    30. End Sub

    Hope this helps...
    Last edited by Siddharth Rout; Sep 9th, 2009 at 09:04 AM. Reason: Spell Check
    A good exercise for the Heart is to bend down and help another up...
    Please Mark your Thread "Resolved", if the query is solved


    MyGear:
    ★ CPU ★ Ryzen 5 5800X
    ★ GPU ★ NVIDIA GeForce RTX 3080 TI Founder Edition
    ★ RAM ★ G. Skill Trident Z RGB 32GB 3600MHz
    ★ MB ★ ASUS TUF GAMING X570 (WI-FI) ATX Gaming
    ★ Storage ★ SSD SB-ROCKET-1TB + SEAGATE 2TB Barracuda IHD
    ★ Cooling ★ NOCTUA NH-D15 CHROMAX BLACK 140mm + 10 of Noctua NF-F12 PWM
    ★ PSU ★ ANTEC HCG-1000-EXTREME 1000 Watt 80 Plus Gold Fully Modular PSU
    ★ Case ★ LIAN LI PC-O11 DYNAMIC XL ROG (BLACK) (G99.O11DXL-X)
    ★ Monitor ★ LG Ultragear 27" 240Hz Gaming Monitor
    ★ Keyboard ★ TVS Electronics Gold Keyboard
    ★ Mouse ★ Logitech G502 Hero

  2. #2
    PowerPoster
    Join Date
    Feb 2006
    Posts
    24,482

    Re: VB6/VBA Creating Access Database via Code

    I see a few things worth mentioning in the ADO example above:

    • ADOX objects should always be late-bound.
    • Where the Precision property is being set I think you really wanted the NumericScale property.
    • Neither Precision nor NumericScale will work as you use them here.
    • Using Jet SQL DDL is generally more versatile than ADOX methods for defining tables.


    Microsoft did a lot of work beginning in MDAC 2.5 to maintain multiple ADO interface versions in each new release. For example the msado15.dll for MDAC 2.8 not only has ADO 2.8 interfaces, it also carries them for 2.7, 2.6, 2.5, and 2.1. This means that a program compiled against ADO 2.5 will continue to work on an ADO 2.8 machine. They even did this as MDAC became DAC with the DAC 6.0 in Vista and Windows 7.

    This was not being done for ADOX however. In the past (i.e. most of Win2K and WinXP's lives) you always had an ADOX version supporting a single interface. This version had settled in at ADOX 2.8 after some time. When Vista RTM shipped though it only contained an ADOX library supporting the version 6.0 interface.

    What this means is that a VB6 program compiled with early binding to ADOX 2.8 on an XP system would not run on Vista RTM (or Vista SP1). And a VB6 program compiled on Vista RTM/SP1 early binding to ADOX 6.0 would not run on any XP (or Win2K, etc.) systems.

    In Vista SP2 this was mildly rememdied: there is now a version of the ADOX library exposing both the 6.0 and the 2.8 interfaces, as well as a typelib for the 2.8 interface.

    There is still a large "pothole" which are those Vista RTM and SP1 systems in the wild. There are also issues running on Win9x systems with an old MDAC release. You can still run across XP systems locked in at ADOX 2.6. DO NOT EARLY BIND ADOX.


    As for Precision (number of digits) and NumericScale (number of dgits to the right of the decimal point), the documentation states:
    NumericScale is read-only for Column objects already appended to a collection.
    NumericScale Property (ADOX)

    The same comment applies to Precision. Maybe the documentation is wrong? I haven't tested this but I suspect it is silently failing as you've used it in your example.


    Using SQL DDL can be a lot more expressive as well as easier to read. It also makes it easier to create inter-table relationships so that we are not treating a Jet MDB as just some collection of ISAM files. You can also define views and stored procedures:
    Code:
        With cnDB
            .Execute "CREATE TABLE Fruits (" _
                   & "FruitID IDENTITY NOT NULL CONSTRAINT PK_FruitID PRIMARY KEY," _
                   & "Fruit TEXT(50) WITH COMPRESSION NOT NULL UNIQUE" _
                   & ")", _
                     , adCmdText
            .Execute "CREATE TABLE Pies (" _
                   & "PieID IDENTITY NOT NULL CONSTRAINT PK_PieID PRIMARY KEY," _
                   & "Pie TEXT(50) WITH COMPRESSION NOT NULL," _
                   & "FruitID INTEGER NOT NULL CONSTRAINT FK_FruitID " _
                   & "REFERENCES Fruits (FruitID)" _
                   & ")", _
                     , adCmdText
            .Execute "CREATE VIEW PiesView (ID, Pie, Fruit) AS " _
                   & "SELECT PieID AS ID, Pie, Fruit " _
                   & "FROM Pies LEFT OUTER JOIN Fruits " _
                   & "ON Pies.FruitID = Fruits.FruitID", _
                     , adCmdText
            .Execute "CREATE PROC InsertPie(NewPie TEXT(50), FruitName TEXT(50)) AS " _
                   & "INSERT INTO Pies (Pie, FruitId) " _
                   & "SELECT NewPie, Fruits.FruitId FROM Fruits " _
                   & "WHERE Fruit = FruitName", _
                     , adCmdText
        End With

  3. #3
    Lively Member Amerigo's Avatar
    Join Date
    Dec 2008
    Location
    PSR B1620-26 c-1
    Posts
    126

    Re: VB6/VBA Creating Access Database via Code

    I am finding this whole database issue to be very confusing. I have a database for my app called ImageDatabase.mdb for storing images. Nothing I have found about creating a database programmatically addresses the types required for images. I get a lot of errors when coping to my code as well. The data base I have was downloaded from elsewhere, but after initial use, it's too big to upload. I am therefore trying to be able to upload my app w/out the database and have the program create it the first time it's ran.
    The database has a table called Pic and 3 Fields?, Columns?, or Rows? named "ID", "Picture", & "Name".

    Here's what I have so far:

    Code:
    Private Sub Album_Load......
    
            If Not IO.File.Exists(Application.StartupPath & "\ImageDatabase.mdb") Then
                CreateDatabase()
            End If
    end sub
    
        Private Sub CreateDatabase()
    
        End Sub
    Alternatively, if possible, I would prefer to have the existing database "deflate" when deleting images.

    Any help would be greatly appreciated.
    Anyone who does not wonder, is either omnipotent or a fool.
    Amerigoware <<<My Projects

  4. #4
    PowerPoster
    Join Date
    Feb 2006
    Posts
    24,482

    Re: VB6/VBA Creating Access Database via Code

    "Deflation" would be a function of a Compact and Repair operation. This can be done via DAO, JRO, or by using Microsoft's JetComp.exe utility.

    Most people store images as a field of type adLongVarBinary... when they actually put them in the database. Of course this is strongly advised againt for many reasons, and most people create a unique name to store the image as a file in a folder related to the database and only store this filename in the database itself.

  5. #5
    Hyperactive Member
    Join Date
    Sep 2014
    Posts
    341

    Re: VB6/VBA Creating Access Database via Code

    Dim tblCollection As Collection
    Can't see what is this variable used for.
    I deleted everything about it and the code still works fine.

    -WIN7 OS, VB6

  6. #6
    Frenzied Member
    Join Date
    May 2014
    Location
    Kallithea Attikis, Greece
    Posts
    1,289

    Re: VB6/VBA Creating Access Database via Code

    ?&Amerigo
    You can pass dib data to a string I do that in M2000 code, you can find in the signature. You have to include cDIBsection class (also define a MDM() global array, usedfor printer properties..If you forget it then an error occur..to remind you). Then search the code for DIBtoSTR and the reverse function. You can place a the bits without compression. You can use it for mini portraits, but a database isn't a store for images.

    The other way is to make links to images...and If you want to "lock" that images, you can scramble the first 100 to 1000 bytes with an XOR function. So when you like to use one, you do the reverse, you open it, and do the reverse again..to scramble it.

    You gain from cDIBsection class because you get some functions to display images with various ways (scale, auto scale with fit in, auto scale with crop). These are old routines, but runs good in vb6. Look that as an idea..

  7. #7
    PowerPoster
    Join Date
    Jun 2013
    Posts
    7,253

    Re: VB6/VBA Creating Access Database via Code

    Quote Originally Posted by bPrice View Post
    Can't see what is this variable used for.
    I deleted everything about it and the code still works fine.

    -WIN7 OS, VB6
    It's not used - though I'd consider what dilettante already said -
    all you need from ADOX (when dealing with JET-DBs) will be the DB-Create-Call,
    which will boil down to this single line here:

    Code:
    CreateObject("ADOX.Catalog").Create "Provider=Microsoft.Jet.OLEDB.4.0;Data Source=" & FileNameOfNewJetDB
    All the rest (e.g. Table-, or Index-creation) is better approached using DDL-SQL-Statements,
    (per: Cnn.Execute SQL_DDL_String)
    learning how to formulate "Create Table ..." or "Create Index ..." or "Alter Table ... Add Column ..."
    will help you with a whole lot of other DB-Engines too ... all will support DDL.

    Olaf

  8. #8
    Hyperactive Member
    Join Date
    Sep 2014
    Posts
    341

    Re: VB6/VBA Creating Access Database via Code

    Quote Originally Posted by Schmidt View Post
    all you need from ADOX (when dealing with JET-DBs) will be the DB-Create-Call,
    Code:
    CreateObject("ADOX.Catalog").Create "Provider=Microsoft.Jet.OLEDB.4.0;Data Source=" & FileNameOfNewJetDB
    Olaf
    Duly noted.



    Quote Originally Posted by Schmidt View Post

    All the rest (e.g. Table-, or Index-creation) is better approached using DDL-SQL-Statements,
    (per: Cnn.Execute SQL_DDL_String)
    learning how to formulate "Create Table ..." or "Create Index ..." or "Alter Table ... Add Column ..."
    will help you with a whole lot of other DB-Engines too ... all will support DDL.

    Olaf
    And thanks for the guidance here. I also checked definition for DML, DDL, DCL and TCL.

    Improviding gradually.


    DML

    DML is abbreviation of Data Manipulation Language. It is used to retrieve, store, modify, delete, insert and update data in database.

    Examples: SELECT, UPDATE, INSERT statements

    DDL

    DDL is abbreviation of Data Definition Language. It is used to create and modify the structure of database objects in database.

    Examples: CREATE, ALTER, DROP statements

    DCL

    DCL is abbreviation of Data Control Language. It is used to create roles, permissions, and referential integrity as well it is used to control access to database by securing it.

    Examples: GRANT, REVOKE statements

    TCL

    TCL is abbreviation of Transactional Control Language. It is used to manage different transactions occurring within a database.

  9. #9
    PowerPoster
    Join Date
    Jun 2013
    Posts
    7,253

    Re: VB6/VBA Creating Access Database via Code

    A nice *.mdb file to play around with, is the "official NorthWind.mdb" ... and I've just uploaded a small
    DDL-Schema-generator (which scans an existing *.mdb, and creates the appropriate DDL-representations
    of the Tables, Indexes and Views it contains) here into the CodeBank, under the following Link:
    http://www.vbforums.com/showthread.p...created-*-mdb)

    Olaf

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •  



Click Here to Expand Forum to Full Width