isCOBOL Database Bridge : EDBI Routines : EDBI Routines for MySQL (InnoDB engine) and MariaDB
EDBI Routines for MySQL (InnoDB engine) and MariaDB
Data mapping (any COMP type could be used, mapping is done according to the digits):
PIC X(n)
VARCHAR(n)
PIC 9(1-2)
TINYINT
PIC 9(3-4)
SMALLINT
PIC 9(5-6)
MEDIUMINT
PIC 9(7-9)
INT
PIC 9(>9)
BIGINT
PIC 9(n)V9(m)
DECIMAL(n+m,m)
PIC S9(n)V9(m)
DECIMAL(n+m,m)
Peculiar jdbc settings:
iscobol.jdbc.autocommit=false
This is set in order to take a lock if issued.
 
The COBOL program shouldn’t use COMMIT and ROLLBACK statements in order to avoid conflicts with the operations performed by EDBI routines.
iscobol.easydb.commit_count=1
This is set in conjunction with iscobol.jdbc.autocommit=false in order to update the table at each WRITE, REWRITE and DELETE statement. Otherwise updates would be made only at CLOSE.
iscobol.jdbc.on_stop_run=commit
Due to the above setting, it’s good practice to instruct the runtime to commit all modifications before exiting.
Lock Timeout:
By default the MySQL and MariaDB drivers wait for locks to be released. If you wish to receive a ‘record locked’ error, you need to issue this statement after the connection has been acquired (e.g. after the opening of the first file):
           EXEC SQL
                EXECUTE IMMEDIATE
                "set innodb_lock_wait_timeout = 0"
           END-EXEC
Note - the above peculiar settings and the need of setting the lock wait timeout are required only if you wish to manage locks natively on the database. If you're working in a Application Server (Thin Client) or File Server environment and you wish to have a full support for locking features, then you may consider handling locks through the Internal lock management.