******************************************************************************* * * SQL catalog verification tool. * * Module %M% Version %I% Date %H% * * (c) Copyright 1998 Ardent Software Inc. - All Rights Reserved * This is unpublished proprietary source code of Ardent Software Inc. * The copyright notice above does not evidence any actual or intended * publication of such source code. * ******************************************************************************* * * Maintenance log - insert most recent change descriptions at top * * Date.... GTAR# WHO Description......................................... * 10/14/98 23801 SAP Change copyrights. * 03/13/96 17797 AGM Replace SH and DOS with OS.EXEC * 01/25/96 17671 LAG Windows NT port * 11/11/94 15285 MGM fix VOC message * 09/29/94 14846 MGM Coordinate UVfile output change for views * 08/18/94 14217 MGM Add view to delete.data, fixed selects * 08/12/94 14217 MGM Add view/association support for Rev. 8 * 02/04/93 12995 DPB WRAP.PRINT call changed to *WRAP.PRINT. * 07/18/93 10131 DPB Initial creation of catalog verification tool. * ******************************************************************************* * * VERIFY.SCHEMA(SchemaOrPath, Fix, Brief, VTables) * * This subroutine will verify the SQL catalog contents for a specific table. * * SchemaOrPath This variable is either the Name of the Schema to be * verified, or the Full Path to the VOC of the Schema to * be verified. * Fix This boolean variable indicates whether or not any * discrepencies found should be fixed. * Brief This boolean variable indicates the amout of output * expected from the subroutine. When turned on only * extrememly critical problems are reported. * VTables This boolean variable indicates whether of not the * tables associated with the schema should be verified. * ******************************************************************************* SUBROUTINE VERIFY.SCHEMA(SchemaOrPath, Fix, Brief, VTables) INCLUDE UNIVERSE.INCLUDE VERIFY.COM INCLUDE UNIVERSE.INCLUDE MACHINE.NAME ****************** ** Windows NT port ** DEFFUN IS.FULLPATH(FILESPEC) CALLING "*IS.FULLPATH" DEFFUN IS.EQPATHS(FILESPEC.A, FILESPEC.B) CALLING "*IS.EQPATHS" DEFFUN GET.DIRNAME(FILESPEC) CALLING "*GET.DIRNAME" DEFFUN GET.BASENAME(FILESPEC) CALLING "*GET.BASENAME" ** ****************** Verbose = NOT(Brief) ;* Opposite of Brief. (Saves opcodes) SchemaName = "" ;* Name of the schema being verified. SchemaPath = "" ;* Path of the schema being verified. FileList = "" Path = "" nodata = 0 HaveData = 0 MoveData = 0 DeleteData = 0 LocalSchema = 0 CatChange = 0 IF IS.FULLPATH(SchemaOrPath) THEN Path = SchemaOrPath SchemaPath = Path:"/VOC" CHKNAME = SchemaPath IF Verbose THEN CALL *WRAP.PRINT("Checking permission.",Width,0,0) GOSUB GETSCHEMA BEGIN CASE CASE GetName = -3 FECount += 1 IF Verbose THEN CALL *WRAP.PRINT("** Account '":SchemaOrPath:"' is not a schema.",Width,0,3) RETURN CASE GetName = -2 FECount += 1 IF Verbose THEN CALL *WRAP.PRINT("** '":SchemaOrPath:"' is not a UniVerse account.",Width,0,3) RETURN CASE GetName = -1 FECount += 1 IF Verbose THEN CALL *WRAP.PRINT("** Unable to verify '":SchemaOrPath:"'.",Width,0,3) RETURN CASE GetName = 0 FECount += 1 IF Verbose THEN CALL *WRAP.PRINT("** '":SchemaOrPath:"' is not an SQL table.",Width,0,3) RETURN END CASE SchemaName = GetName sid = SchemaName READ srec FROM uvschema,sid THEN IF NOT(IS.EQPATHS(Path, srec<2>)) THEN ECount += 1 IF Verbose THEN CALL *WRAP.PRINT("* Possible moved or duplicate schema.",Width,0,2) CHKNAME = srec<2>:"/VOC" GOSUB GETSCHEMA BEGIN CASE CASE GetName = -3 FECount += 1 IF Verbose THEN CALL *WRAP.PRINT("** Account '":SchemaOrPath:"' is not a schema.",Width,0,3) RETURN CASE GetName = SchemaName FECount += 1 IF Verbose THEN CALL *WRAP.PRINT("** ":SchemaOrPath:" is a duplicate schema. It cannot have data in the SQL catalog.",Width,0,3) RETURN CASE GetName = -1 FECount += 1 IF Verbose THEN CALL *WRAP.PRINT("** Schema might be a duplicate.",Width,0,3) IF Verbose THEN CALL *WRAP.PRINT("** Unable to verify '":SchemaOrPath:"'.",Width,0,3) RETURN CASE GetName = -2 IF Verbose THEN CALL *WRAP.PRINT("Moved Schema.",Width,0,0) MoveData = 1 CASE GetName = 0 IF Verbose THEN CALL *WRAP.PRINT("Moved Schema.",Width,0,0) MoveData = 1 CASE GetName # SchemaName IF Verbose THEN CALL *WRAP.PRINT("Moved Schema.",Width,0,0) MoveData = 1 END CASE END ELSE HaveData = 1 END END ELSE CALL *WRAP.PRINT("* No SQL catalog data exists for schema found at '":Path:"'.",Width,0,2) nodata = 1 END END ELSE IF SchemaOrPath = "" AND @SCHEMA = "" THEN FECount += 1 IF Verbose THEN CALL *WRAP.PRINT("** The current account is not a schema." ,Width,0,3) RETURN END ELSE IF SchemaOrPath = "" THEN LocalSchema = 1 SchemaOrPath = @SCHEMA SchemaName = @SCHEMA ************************************** * Get the current working directory. * ************************************** Path = @PATH SchemaPath = Path:"/VOC" END sid = SchemaOrPath IF Verbose THEN CALL *WRAP.PRINT("Checking permission.",Width,0,0) READ srec FROM uvschema,sid THEN HaveData = 1 Path = srec<2> SchemaPath = Path:"/VOC" IF NOT(LocalSchema) THEN SchemaName = SchemaOrPath CHKNAME = SchemaPath GOSUB GETSCHEMA BEGIN CASE CASE GetName = -3 ECount += 1 IF Verbose THEN CALL *WRAP.PRINT("* The VOC at '":Path:"' is not a schema VOC.",Width,0,2) DeleteData = 1 CASE GetName = -1 FECount += 1 IF Verbose THEN CALL *WRAP.PRINT("** Unable to verify '":SchemaOrPath:"'.",Width,0,3) RETURN CASE GetName = -2 ECount += 1 IF Verbose THEN CALL *WRAP.PRINT("* '":Path:"' is not a UniVerse account.",Width,0,3) DeleteData = 1 CASE GetName = 0 IF Verbose THEN CALL *WRAP.PRINT("* ":Path:"/VOC is not an SQL table.",Width,0,3) DeleteData = 1 CASE GetName # SchemaOrPath ECount += 1 IF Verbose THEN CALL *WRAP.PRINT("* Cannot find schema '":SchemaOrPath:"'.",Width,0,2) DeleteData = 1 CASE 1 SchemaName = GetName END CASE END END ELSE IF LocalSchema THEN nodata = 1 END ELSE FECount += 1 IF Verbose THEN CALL *WRAP.PRINT("** No SQL catalog data for schema '":SchemaOrPath:"' in UV_SCHEMA.",Width,0,3) RETURN END END END IF nodata = 1 THEN ECount += 1 IF Fix THEN IF Verbose THEN CALL *WRAP.PRINT("* Creating catalog data for the schema '":SchemaOrPath:"'.",Width,0,2) OPENPATH SchemaPath TO tmpfile ELSE CALL *WRAP.PRINT("** Unable to open '":SchemaPath:"'.",Width,0,3) RETURN END STATUS statrec FROM tmpfile ELSE CALL *WRAP.PRINT("** Cannot get status.",Width,0,3) RETURN END CLOSE tmpfile srec<1> = statrec<8> srec<2> = Path WRITE srec ON uvschema,sid END ELSE IF Verbose THEN CALL *WRAP.PRINT("* Catalog data for schema '":SchemaOrPath:"' should be created.",Width,0,2) END ELSE IF MoveData = 1 THEN ECount += 1 IF Fix THEN GOSUB MOVE.DATA END ELSE IF Verbose THEN CALL *WRAP.PRINT("* Data for the schema '":SchemaOrPath:"' should be moved.",Width,0,2) END ELSE IF DeleteData = 1 THEN ECount += 1 IF Fix THEN GOSUB DELETE.DATA END ELSE IF Verbose THEN CALL *WRAP.PRINT("* Data for the schema '":SchemaOrPath:"' should be deleted.",Width,0,2) RETURN END ************************************************************************ * Open the file and get the status. Use the status to verify the owner * * of the file against the SICA and the catalog data. * ************************************************************************ OPENPATH SchemaPath TO tmpfile ELSE FECount += 1 CALL *WRAP.PRINT("** You don't have the correct permissions to verify this schema.",Width,0,3) RETURN END STATUS statrec FROM tmpfile ELSE FECount += 1 CALL *WRAP.PRINT("** Cannot get status.",Width,0,3) RETURN END CLOSE tmpfile IF srec<1> # statrec<8> THEN ECount += 1 IF Fix THEN IF Verbose THEN CALL *WRAP.PRINT("* Changing schema owner to match actual owner.",Width,0,2) srec<1> = statrec<8> CatChange = 1 END ELSE IF Verbose THEN CALL *WRAP.PRINT("* OS owner (of VOC) does not agree with catalog specified owner.",Width,0,2) END IF CatChange = 1 THEN WRITE srec ON uvschema,sid END END IF VTables THEN GOSUB BUILDLIST IF DCOUNT(FileList,@FM) = 0 AND DCOUNT(PFileList,@FM) = 0 AND DCOUNT(VFileList,@FM) = 0 THEN IF Verbose THEN CALL *WRAP.PRINT("No tables found for the schema '":SchemaName:"'.",Width,0,0) END FOR I = 1 to DCOUNT(FileList,@FM) IF Verbose THEN CALL *WRAP.PRINT(" ",Width,5,0) IF Verbose THEN CALL *WRAP.PRINT("Verifying table '":FileList:"'.",Width,0,0) CALL *VERIFY.TABLE(FileList, Path:@FM:SchemaName, Fix, Brief, 0) NEXT I FOR I = 1 to DCOUNT(VFileList,@FM) IF Verbose THEN CALL *WRAP.PRINT(" ",Width,5,0) IF Verbose THEN CALL *WRAP.PRINT("Verifying view '":VFileList:"'.",Width,0,0) CALL *VERIFY.TABLE(VFileList, Path:@FM:SchemaName, Fix, Brief, 1) NEXT I FOR I = 1 to DCOUNT(PFileList,@FM) IF I = 1 THEN IF Verbose THEN CALL *WRAP.PRINT(" ",Width,5,0) IF Verbose THEN CALL *WRAP.PRINT("These tables/views could not be verified (due to OS or SQL permissions):.",Width,0,0) END FECount += 1 IF Verbose THEN CALL *WRAP.PRINT("** ":PFileList,Width,0,3) NEXT I END RETURN GETSCHEMA: EXECUTE OS.EXEC: " '":UV.ROOT:"/bin/UVfile -s ":CHKNAME:"'" CAPTURING junk IF junk<1>[1,8] = "[EACCES]" THEN CALL *WRAP.PRINT("* Permission denied on Schema '":CHKNAME:"'.",Width,0,2) GetName = -1 END ELSE IF INDEX(junk,"Permission denied",1) THEN CALL *WRAP.PRINT("* Permission denied on Schema '":CHKNAME:"'.",Width,0,2) GetName = -1 END ELSE IF junk<1>[LEN(junk<1>)-24,LEN(junk<1>)] = "No such file or directory" THEN GetName = -2 END ELSE IF junk = "" THEN GetName = 0 END ELSE junk = CONVERT(" ",@FM,junk<2>) GetName = junk IF GetName = "" THEN GetName = -3 END END RETURN *************************************************************************** * There needs to be valid data in the variable Path and SchemaName for * this routine to work. *************************************************************************** BUILDLIST: IF Verbose THEN PRINT ON Pchan "Building table list.": ****************** ** Windows NT port ** IF OS.TYPE = "UNIX" THEN EXECUTE "SH -c 'ls ":Path:"'" CAPTURING dlist END ELSE EXECUTE "DOS /C '":UV.ROOT:"/bin/uvwalk ":Path:"'" CAPTURING dlist END ** ****************** IF Verbose THEN PRINT ".": dlist = dlist[1,LEN(dlist)-1] EXECUTE 'SELECT UV_TABLES WITH TABLE_SCHEMA = "':SchemaName:'" AND TABLE_TYPE = "BASE TABLE"' RTNLIST slist CAPTURING junk EXECUTE 'SELECT UV_TABLES WITH TABLE_SCHEMA = "':SchemaName:'" AND TABLE_TYPE = "VIEW"' RTNLIST vlist CAPTURING junk IF Verbose THEN PRINT ".": FileList = "" VFileList = "" PFileList = "" bounds = DCOUNT(dlist,@FM) FOR i = 1 to bounds IF dlist[1,2] = "D_" THEN CONTINUE CHKNAME = Path:"/":dlist GOSUB EXISTS BEGIN CASE CASE EXVAL = 2 LOCATE(dlist,FileList;tmp) ELSE IF Verbose THEN PRINT On Pchan ".": INS Path:"/":dlist BEFORE FileList<-1> END CASE EXVAL = 3 LOCATE(dlist,PFileList;tmp) ELSE IF Verbose THEN PRINT On Pchan ".": INS Path:"/":dlist BEFORE PFileList<-1> END CASE EXVAL = 4 LOCATE(dlist,VFileList;tmp) ELSE IF Verbose THEN PRINT On Pchan ".": INS Path:"/":dlist BEFORE VFileList<-1> END END CASE NEXT i done = 0 LOOP READNEXT id FROM slist ELSE done = 1 WHILE NOT(done) DO name = CONVERT(@TM,@FM,id) READ trec FROM uvtables,id ELSE CONTINUE Tpath = GET.DIRNAME(trec<6>) LOCATE(trec<6>,FileList;tmp) ELSE LOCATE(trec<6>,PFileList;tmp) ELSE IF Verbose THEN PRINT On Pchan ".": IF Tpath = Path THEN INS name<2> BEFORE FileList<-1> END ELSE INS trec<6> BEFORE FileList<-1> END END END REPEAT done = 0 LOOP READNEXT id FROM vlist ELSE done = 1 WHILE NOT(done) DO name = CONVERT(@TM,@FM,id) READ trec FROM uvtables,id ELSE CONTINUE Tpath = GET.DIRNAME(trec<6>) LOCATE(trec<6>,VFileList;tmp) ELSE LOCATE(trec<6>,PFileList;tmp) ELSE IF Verbose THEN PRINT On Pchan ".": IF Tpath = Path THEN INS name<2> BEFORE VFileList<-1> END ELSE INS trec<6> BEFORE VFileList<-1> END END END REPEAT IF Verbose THEN PRINT On Pchan "Done." RETURN ******************************************************************************* * * * Given a file name, run UVfile on it and return one of the following values: * * 0 The file doesn't exists, or is not a uniVerse file. * * 1 This is a normal uniVerse file. * * 2 This is a uniVerse SQL file. * * 3 We do not have the correct permissions to access this file. * * * ******************************************************************************* EXISTS: EXECUTE OS.EXEC:" '":UV.ROOT:"/bin/UVfile ":CHKNAME:"'" CAPTURING junk EXVAL = 1 IF junk[1,8] = "[EACCES]" THEN EXVAL = 3 IF junk[1,18] = "Permission Denied." THEN EXVAL = 3 IF junk<1> = CHKNAME:": No such file or directory" THEN EXVAL = 0 IF junk<1> = CHKNAME:": Not a uniVerse file." THEN EXVAL = 0 IF junk<1>[LEN(CHKNAME)+1,28] = ": Dynamic file (uniVerse SQL" THEN EXVAL = 2 IF junk<1>[LEN(CHKNAME)+1,27] = ": Hashed file (uniVerse SQL" THEN EXVAL = 2 IF junk<1>[LEN(CHKNAME)+9,20] = ": View (UV type 41)." THEN EXVAL = 4 RETURN DELETE.DATA: IF Verbose THEN CALL *WRAP.PRINT("* Deleting catalog data for schema '":SchemaOrPath:"'.",Width,0,2) DELETE uvschema,SchemaName EXECUTE "SELECT UV_TABLES WITH TABLE_SCHEMA = ":SchemaName:"" RTNLIST tmplist CAPTURING junk done = 0 LOOP READNEXT id FROM tmplist ELSE done = 1 WHILE NOT(done) DO name = convert(@TM,@FM,id) IF Verbose THEN CALL *WRAP.PRINT("* Deleting table data for '":name<2>:"'.",Width,0,2) DELETE uvtables,id REPEAT EXECUTE "SELECT UV_COLUMNS WITH TABLE_SCHEMA = ":SchemaName:"" RTNLIST tmplist CAPTURING junk done = 0 LOOP READNEXT id FROM tmplist ELSE done = 1 WHILE NOT(done) DO name = convert(@TM,@FM,id) IF Verbose THEN CALL *WRAP.PRINT("* Deleting columns data for '":name<3>:"'.",Width,0,2) DELETE uvcolumns,id REPEAT EXECUTE "SELECT UV_ASSOC WITH ASSOC_SCHEMA = ":SchemaName:"" RTNLIST tmplist CAPTURING junk done = 0 LOOP READNEXT id FROM tmplist ELSE done = 1 WHILE NOT(done) DO name = convert(@TM,@FM,id) IF Verbose THEN CALL *WRAP.PRINT("* Deleting association data for '":name<2>:"'.",Width,0,2) DELETE uvassoc,id REPEAT EXECUTE "SELECT UV_VIEWS WITH VIEW_SCHEMA = ":SchemaName:"" RTNLIST tmplist CAPTURING junk done = 0 LOOP READNEXT id FROM tmplist ELSE done = 1 WHILE NOT(done) DO name = convert(@TM,@FM,id) IF Verbose THEN CALL *WRAP.PRINT("* Deleting view data for '":name<2>:"'.",Width,0,2) DELETE uvview,id REPEAT ****************************************************** * Delete all UV_USERS ownership data for this table. * ****************************************************** EXECUTE "SELECT UV_USERS WITH SCHEMAS LIKE ...":SchemaName:"..." RTNLIST rlst CAPTURING junk SavRec = 0 done = 0 LOOP READNEXT id FROM rlst ELSE done = 1 WHILE NOT(done) DO READ delrec FROM uvusers,id ELSE CONTINUE BOUNDS = DCOUNT(delrec<5>,@VM) CNT = 1 LOOP WHILE CNT <= BOUNDS DO IF delrec<4,CNT> = SchemaName THEN IF Verbose THEN CALL *WRAP.PRINT("* Deleting ownership record for user '":id:"' on table '":delrec<5,CNT>:"'.",Width,0,2) DEL delrec<5,CNT> DEL delrec<4,CNT> BOUNDS = BOUNDS - 1 SavRec = 1 END ELSE CNT = CNT + 1 END REPEAT IF SavRec THEN WRITE delrec ON uvusers,id ELSE CALL *WRAP.PRINT("* Problems with the write. Unable to delete ownership record for user '":id:"'.",Width,0,2) SavRec = 0 END REPEAT ******************************************************* * Delete all UV_USERS permission data for this table. * ******************************************************* EXECUTE "SELECT UV_USERS WITH PERM_SCHEMAS LIKE ...":SchemaName:"..." RTNLIST rlst CAPTURING junk SavRec = 0 done = 0 LOOP READNEXT id FROM rlst ELSE done = 1 WHILE NOT(done) DO READ delrec FROM uvusers,id ELSE CONTINUE BOUNDS = DCOUNT(delrec<7>,@VM) CNT = 1 LOOP WHILE CNT <= BOUNDS DO IF delrec<6,CNT> = SchemaName THEN IF Verbose THEN CALL *WRAP.PRINT("* Deleting permission record for user '":id:"' on table '":delrec<7,CNT>:"'.",Width,0,2) DEL delrec<7,CNT> DEL delrec<6,CNT> BOUNDS = BOUNDS - 1 SavRec = 1 END ELSE CNT = CNT + 1 END REPEAT IF SavRec THEN WRITE delrec ON uvusers,id ELSE CALL *WRAP.PRINT("* Problems with the write. Unable to delete permission record for users '":id:"'.",Width,0,2) SavRec = 0 END REPEAT RETURN MOVE.DATA: IF Verbose THEN CALL *WRAP.PRINT("* Moving data for schema '":SchemaName:"'.",Width,0,2) srec<2> = Path WRITE srec ON uvschema,sid EXECUTE "SELECT UV_TABLES WITH TABLE_SCHEMA = ":SchemaName:"" RTNLIST tlist CAPTURING junk done = 0 LOOP READNEXT id FROM tlist ELSE done = 1 WHILE NOT(done) DO READ trec FROM uvtables,id ELSE CONTINUE name = convert(@TM,@FM,id) IF Verbose THEN CALL *WRAP.PRINT("* Moving data for table '":name<2>:"'.",Width,0,2) trec<6> = Path:"/":GET.BASENAME(trec<6>) trec<7> = Path:"/":GET.BASENAME(trec<7>) WRITE trec ON uvtables,id REPEAT RETURN