tldm-universe/Ardent/UV/APP.PROGS/VERF.CAT.B
2024-09-09 17:51:08 -04:00

981 lines
38 KiB
Plaintext
Executable File

*******************************************************************************
*
* 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/26/96 17337 JBG UV_VIEWS TABLE is MULTIVALUED in Rel 9
* 03/13/96 17797 AGM Replace DOS and SH with OS.EXEC
* 01/25/96 17671 LAG Windows NT port
* 09/29/94 14846 MGM Coordinate UVfile output change for views
* 08/19/94 14217 MGM full UV_VIEWS support
* 08/12/94 14217 MGM Add view/association support for Rev. 8
* 08/03/93 11938 DPB Changed various messages for consistency.
* 07/18/93 10131 DPB Initial creation of catalog verification tool.
*
*******************************************************************************
*
* VERIFY.CATALOG(Fix, Brief)
*
* This subroutine will verify the internal consistency of the SQL catalog.
*
* 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.
*
*******************************************************************************
SUBROUTINE VERIFY.CATALOG(Fix, Brief)
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)
IF Verbose THEN CALL *WRAP.PRINT("Verifying the internal consistency of the SQL catalog.",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT("Checking UV_USERS for incorrect table information in the ownership lists.",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
SSELECTV uvusers TO listvar
done = 0
LOOP
READNEXT id FROM listvar ELSE done = 1
WHILE NOT(done) DO
READ userrec FROM uvusers,id ELSE CONTINUE
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT("Verifying ownership list for user '":id:"'.",Width,0,0)
RecChange = 0
CNT = DCOUNT(userrec<5>,@VM)
FileList = ""
FOR I = 1 to CNT
File = userrec<4,I>:" ":userrec<5,I>
fid = userrec<4,I>:@TM:userrec<5,I>
LOCATE(File,FileList;tmp;"AL")
THEN
ECount += 1
IF Fix
THEN
IF Verbose THEN CALL *WRAP.PRINT("* Deleteing duplicate ownership entry for user '":id:"' on table '":userrec<5,I>:"' in schema '":userrec<4,I>:"'.",Width,0,2)
RecChange = 1
END
ELSE IF Verbose THEN CALL *WRAP.PRINT("* Found a duplicate ownership entry for user '":id:"' on table '":userrec<5,I>:"' in schema '":userrec<4,I>:"'.",Width,0,2)
END
ELSE
READ trec FROM uvtables,fid
THEN
FileList = INSERT(FileList,tmp;File)
END
ELSE
ECount += 1
IF Fix
THEN
RecChange = 1
IF Verbose THEN CALL *WRAP.PRINT("* Deleting the ownership entry for user '":id:"' on the table '":userrec<5,I>:"' in schema '":userrec<4,I>:"' which does not have UV_TABLES catalog data.",Width,0,2)
END
ELSE IF Verbose THEN CALL *WRAP.PRINT("* Found an ownership entry for user '":id:"' on the table '":userrec<5,I>:"' in schema '":userrec<4,I>:"' which does not have UV_TABLES catalog data.",Width,0,2)
END
END
NEXT I
IF Fix AND RecChange
THEN
userrec<4> = ""
userrec<5> = ""
CNT = DCOUNT(FileList,@FM)
FOR I = 1 to CNT
File = FileList<I>
File = CONVERT(" ",@FM,File)
userrec<4,I> = File<1>
userrec<5,I> = File<2>
NEXT I
WRITE userrec ON uvusers,id
END
REPEAT
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT("Checking UV_USERS for incorrect table information in the permission lists.",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
SSELECTV uvusers TO listvar
done = 0
LOOP
READNEXT id FROM listvar ELSE done = 1
WHILE NOT(done) DO
READ userrec FROM uvusers,id ELSE CONTINUE
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT("Verifying permission list for user '":id:"'.",Width,0,0)
RecChange = 0
CNT = DCOUNT(userrec<7>,@VM)
FileList = ""
FOR I = 1 to CNT
File = userrec<6,I>:" ":userrec<7,I>
fid = userrec<6,I>:@TM:userrec<7,I>
LOCATE(File,FileList;tmp;"AL")
THEN
ECount += 1
IF Fix
THEN
IF Verbose THEN CALL *WRAP.PRINT("* Deleteing duplicate permission entry for user '":id:"' on table '":userrec<7,I>:"' in schema '":userrec<6,I>:"'.",Width,0,2)
RecChange = 1
END
ELSE IF Verbose THEN CALL *WRAP.PRINT("* Found a duplicate permission entry for user '":id:"' on table '":userrec<7,I>:"' in schema '":userrec<6,I>:"'.",Width,0,2)
END
ELSE
READ trec FROM uvtables,fid
THEN
FileList = INSERT(FileList,tmp;File)
END
ELSE
ECount += 1
IF Fix
THEN
RecChange = 1
IF Verbose THEN CALL *WRAP.PRINT("* Deleting the permission entry for user '":id:"' on the table '":userrec<7,I>:"' in schema '":userrec<6,I>:"' which does not have UV_TABLES catalog data.",Width,0,2)
END
ELSE IF Verbose THEN CALL *WRAP.PRINT("* Found a permission entry for user '":id:"' on the table '":userrec<7,I>:"' in schema '":userrec<6,I>:"' which does not have UV_TABLES catalog data.",Width,0,2)
END
END
NEXT I
IF Fix AND RecChange
THEN
userrec<6> = ""
userrec<7> = ""
CNT = DCOUNT(FileList,@FM)
FOR I = 1 to CNT
File = FileList<I>
File = CONVERT(" ",@FM,File)
userrec<6,I> = File<1>
userrec<7,I> = File<2>
NEXT I
WRITE userrec ON uvusers,id
END
REPEAT
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT("Checking UV_USERS for invalid users or users with duplicate user ids.",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
SSELECTV uvusers TO listvar
done = 0
Ulist = ""
UNlist = ""
LOOP
READNEXT id FROM listvar ELSE done = 1
WHILE NOT(done) DO
CHKNAME = id
UID = ""
GOSUB GETUSER
IF UID = -1
THEN
ECount += 1
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT("* '":id:"' is not a valid user.",Width,0,2)
CONTINUE
END
LOCATE(UID,Ulist;tmp;"AR")
THEN
ECount += 1
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT("* '":id:"' has the same user id as '":UNlist<tmp>:"'.",Width,0,2)
END
ELSE
Ulist = INSERT(Ulist,tmp;UID)
UNlist = INSERT(UNlist,tmp;id)
END
REPEAT
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT("Checking UV_TABLES for incorrect table information.",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
SSELECTV uvtables TO listvar
Flist = ""
FPlist = ""
Dlist = ""
done = 0
LOOP
READNEXT id FROM listvar ELSE done = 1
WHILE NOT(done) DO
READ trec FROM uvtables,id ELSE CONTINUE
IsaView = 0
SQLobject = 'table'
IF trec<2> = "ASSOCIATION"
THEN
key = id[1,INDEX(id,trec<3>,1)+LEN(trec<3>)-1]
assocname = id[INDEX(id,key,1)+LEN(key)+1,LEN(id)]
name = CONVERT(@TM,@FM,key)
READ atrec FROM uvtables,key
ELSE
ECount += 1
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT("* There is no Base Table which refers to the UV_TABLES association data for the association '":assocname:"' on table '":name<2>:" (":name<1>:")'.",Width,0,2)
END
CONTINUE
END
IF trec<2> = "VIEW"
THEN
IsaView = 1
SQLobject = 'view'
END
name = CONVERT(@TM,@FM,id)
READ srec FROM uvschema,name<1>
ELSE
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
ECount += 1
IF Fix
THEN
IF Verbose THEN CALL *WRAP.PRINT("* The ":SQLobject:" '":name<2>:" (":name<1>:")' is in a schema which does not have UV_SCHEMA data. Deleting all SQL catalog data for this ":SQLobject:".",Width,0,2)
tname = name
key = id
catrec = trec
GOSUB DELETE.DATA
INS key BEFORE Dlist<-1>
END
ELSE
IF Verbose THEN CALL *WRAP.PRINT("* The ":SQLobject:" '":name<2>:" (":name<1>:")' is in a schema which does not have UV_SCHEMA data. All SQL catalog data for this ":SQLobject:" should be deleted.",Width,0,2)
INS id BEFORE Dlist<-1>
END
CONTINUE
END
CHKNAME = trec<6>
GOSUB EXISTS
BEGIN CASE
CASE EXVAL = 3
IF Verbose THEN CALL *WRAP.PRINT("** Unable to check ":SQLobject:" '":name<2>:" (":name<1>:")'. Leaving its UV_TABLES record alone.",Width,0,3)
FECount += 1
CASE EXVAL = 1
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
ECount += 1
IF Fix
THEN
IF Verbose THEN CALL *WRAP.PRINT("* '":name<2>:" (":name<1>:")' points to a non-SQL file. Deleting all SQL catalog data for this ":SQLobject:".",Width,0,2)
tname = name
key = id
catrec = trec
GOSUB DELETE.DATA
INS key BEFORE Dlist<-1>
END
ELSE
IF Verbose THEN CALL *WRAP.PRINT("* '":name<2>:" (":name<1>:")' points to a non-SQL file. All SQL catalog data for this ":SQLobject:" should be deleted.",Width,0,2)
INS id BEFORE Dlist<-1>
END
CONTINUE
CASE EXVAL = 0
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
ECount += 1
IF Fix
THEN
IF Verbose THEN CALL *WRAP.PRINT("* '":name<2>:" (":name<1>:")' points to a non-existent file. Deleting all SQL catalog data for this ":SQLobject:".",Width,0,2)
tname = name
key = id
catrec = trec
GOSUB DELETE.DATA
INS key BEFORE Dlist<-1>
END
ELSE
IF Verbose THEN CALL *WRAP.PRINT("* '":name<2>:" (":name<1>:")' points to a non-existent file. All SQL catalog data for this ":SQLobject:" should be deleted.",Width,0,2)
INS id BEFORE Dlist<-1>
END
CONTINUE
END CASE
LOCATE(trec<6>,FPlist;tmp;"AL")
THEN
ECount += 1
name2 = CONVERT(@TM,@FM,Flist<tmp>)
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT("* '":name<2>:" (":name<1>:")' has the same path as '":name2<2>:" (":name2<1>:")'.",Width,0,2)
CHKNAME = trec<6>
GOSUB GETSICA
IF Sica<NAME,TABLENAME>=name<2> AND Sica<NAME,SCHEMANAME>=name<1>
THEN
IF Fix
THEN
IF Verbose THEN CALL *WRAP.PRINT("* '":name<2>:" (":name<1>:")' is correct. Deleting all SQL catalog data for '":name2<2>:" (":name2<1>:")'.",Width,0,2)
tname = name2
key = Flist<tmp>
READ catrec FROM uvtables,key ELSE CONTINUE
GOSUB DELETE.DATA
INS key BEFORE Dlist<-1>
Flist<tmp> = id
END
ELSE
IF Verbose THEN CALL *WRAP.PRINT("* '":name<2>:" (":name<1>:")' is correct. All SQL catalog data for '":name2<2>:" (":name2<1>:")' should be deleted.",Width,0,2)
INS Flist<tmp> BEFORE Dlist<-1>
END
END
ELSE IF Sica<NAME,TABLENAME>=name2<2> AND Sica<NAME,SCHEMANAME>=name2<1>
THEN
IF Fix
THEN
IF Verbose THEN CALL *WRAP.PRINT("* '":name2<2>:" (":name2<1>:")' is correct. Deleting all SQL catalog data for '":name<2>:" (":name<1>:")'.",Width,0,2)
tname = name
key = id
catrec = trec
GOSUB DELETE.DATA
INS key BEFORE Dlist<-1>
END
ELSE
IF Verbose THEN CALL *WRAP.PRINT("* '":name2<2>:" (":name2<1>:")' is correct. All SQL catalog data for '":name<2>:" (":name<1>:")' should be deleted.",Width,0,2)
INS id BEFORE Dlist<-1>
END
END
ELSE
IF Fix
THEN
IF Verbose THEN CALL *WRAP.PRINT("* Both UV_TABLES records are incorrect. Deleting all catalog data for both UV_TABLES records and creating new catalog data for the ":SQLobject:".",Width,0,2)
tname = name
key = id
catrec = trec
GOSUB DELETE.DATA
INS key BEFORE Dlist<-1>
tname = name2
key = Flist<tmp>
READ catrec FROM uvtables,key ELSE CONTINUE
GOSUB DELETE.DATA
INS key BEFORE Dlist<-1>
CALL *VERIFY.TABLE(trec<6>,Sica<NAME,SCHEMANAME>,1,Brief,IsaView)
Flist<tmp> = Sica<NAME,TABLENAME>
END
ELSE
IF Verbose THEN CALL *WRAP.PRINT("* Both UV_TABLES records are incorrect. All catalog data for both of them should be deleted, and new catalog data for the ":SQLobject:" created.",Width,0,2)
INS id BEFORE Dlist<-1>
INS Flist<tmp> BEFORE Dlist<-1>
END
END
END
ELSE
FPlist = INSERT(FPlist,tmp;trec<6>)
Flist = INSERT(Flist,tmp;id)
IF trec<5> # ""
THEN
ViewChange = 0
newViews = trec<5>
FOR I = 1 to DCOUNT(trec<5>,@VM)
ViewN = trec<5,I>[INDEX(trec<5,I>,".",1)+1,LEN(trec<5,I>)]
ViewS = trec<5,I>[1,INDEX(trec<5,I>,".",1)-1]
Vkey = ViewS:@TM:ViewN
READ viewrec2 FROM uvview,Vkey
ELSE
ECount += 1
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Fix
THEN
LOCATE(trec<5,I>,newViews,1;ttmp)
THEN
IF Verbose THEN CALL *WRAP.PRINT("* Deleting '":ViewN:" (":ViewS:")' from (column VIEWS) in UV_TABLES for ":SQLobject:" '":name<2>:" (":name<1>:")'.",Width,0,2)
DEL newViews<1,ttmp>
ViewChange = 1
END
END
ELSE IF Verbose THEN CALL *WRAP.PRINT("* ":SQLobject:" '":name<2>:" (":name<1>:")' (column VIEWS) does not have a record in UV_VIEWS for '":ViewN:" (":ViewS:")'.",Width,0,2)
END
NEXT I
IF ViewChange AND Fix
THEN
trec<5> = newViews
WRITE trec ON uvtables,id
END
END
END
REPEAT
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT("Checking UV_COLUMNS for incorrect column information.",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
SSELECTV uvcolumns TO listvar
done = 0
CCount = 0
LOOP
READNEXT id FROM listvar ELSE done = 1
WHILE NOT(done) DO
tname = id[1,INDEX(id,@TM,2)-1]
name = CONVERT(@TM,@FM,id)
SQLobject = 'table'
LOCATE(tname,Flist;tmp)
THEN
SQLobject = 'table'
READ trec FROM uvtables,Flist<tmp> ELSE CONTINUE
IF trec<2> = "VIEW" THEN SQLobject = 'view'
LOCATE(name<3>,trec,4;tmp)
ELSE
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Fix
THEN
IF Verbose THEN CALL *WRAP.PRINT("* Column '":name<3>:"' does not have data in the UV_TABLES record for the ":SQLobject:" '":name<2>:" (":name<1>:")'. Deleting UV_COLUMNS data for this column.",Width,0,2)
DELETE uvcolumns,id
END
ELSE
IF Verbose THEN CALL *WRAP.PRINT("* Column '":name<3>:"' does not have data in the UV_TABLES record for the ":SQLobject:" '":name<2>:" (":name<1>:")'. UV_COLUMNS data for this column should be deleted.",Width,0,2)
END
END
END
ELSE
LOCATE(tname,Dlist;tmp)
ELSE
CCount += 1
ECount += 1
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Fix
THEN
IF Verbose THEN CALL *WRAP.PRINT("* Column '":name<3>:"' points to ":SQLobject:" '":name<2>:" (":name<1>:")' which does not have UV_TABLES data. Deleting UV_COLUMNS data for this column.",Width,0,2)
DELETE uvcolumns,id
END
ELSE
IF Verbose THEN CALL *WRAP.PRINT("* Column '":name<3>:"' points to ":SQLobject:" '":name<2>:" (":name<1>:")' which does not have UV_TABLES data. UV_COLUMNS data for this column should be deleted.",Width,0,2)
END
END
END
REPEAT
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT("Checking UV_SCHEMA for incorrect schema information.",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
SSELECTV uvschema TO listvar
Slist = ""
SPlist = ""
done = 0
LOOP
READNEXT id FROM listvar ELSE done = 1
WHILE NOT(done) DO
READ srec FROM uvschema,id ELSE CONTINUE
LOCATE(srec<2>,SPlist;tmp;"AL")
THEN
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
ECount +=1
IF Verbose THEN CALL *WRAP.PRINT("* Schema '":id:"' has the same path as schema '":Slist<tmp>:"'.",Width,0,2)
CHKNAME = srec<2>:"/VOC"
GOSUB GETSCHEMA
BEGIN CASE
CASE GetName = -3
ECount += 1
IF Verbose THEN CALL *WRAP.PRINT("* '":srec<2>:"' is not a schema.",Width,0,2)
IF Fix
THEN
IF Verbose THEN CALL *WRAP.PRINT("* Neither '":id:"' nor '":Slist<tmp>:"' is a valid schema. Deleting schema data for them both.",Width,0,2)
CALL *VERIFY.SCHEMA(id,Fix,Brief,1)
CALL *VERIFY.SCHEMA(Slist<tmp>,Fix,Brief,1)
Slist = DELETE(Slist,tmp)
SPlist = DELETE(SPlist,tmp)
END
ELSE IF Verbose THEN CALL *WRAP.PRINT("* Neither '":id:"' nor '":Slist<tmp>:"' is a valid schema. Schema data for both should be deleted.",Width,0,2)
CONTINUE
CASE GetName = -2
ECount += 1
IF Verbose THEN CALL *WRAP.PRINT("* There is no schema '":srec<2>:"'.",Width,0,2)
IF Fix
THEN
IF Verbose THEN CALL *WRAP.PRINT("* Neither '":id:"' nor '":Slist<tmp>:"' is a valid schema. Deleting schema data for them both.",Width,0,2)
CALL *VERIFY.SCHEMA(id,Fix,Brief,1)
CALL *VERIFY.SCHEMA(Slist<tmp>,Fix,Brief,1)
Slist = DELETE(Slist,tmp)
SPlist = DELETE(SPlist,tmp)
END
ELSE IF Verbose THEN CALL *WRAP.PRINT("* Neither '":id:"' nor '":Slist<tmp>:"' is a valid schema. Schema data for both should be deleted.",Width,0,2)
CONTINUE
CASE GetName = -1
ECount += 1
IF Verbose THEN CALL *WRAP.PRINT("* Unable to verify '":srec<2>:"'.",Width,0,2)
IF Verbose THEN CALL *WRAP.PRINT("* Leaving the schemas with duplicate paths alone.",Width,0,2)
CONTINUE
CASE GetName = 0
ECount += 1
IF Verbose THEN CALL *WRAP.PRINT("* '":srec<2>:"' is not an SQL table.",Width,0,2)
IF Fix
THEN
IF Verbose THEN CALL *WRAP.PRINT("* Neither '":id:"' nor '":Slist<tmp>:"' is a valid schema. Deleting schema data for them both.",Width,0,2)
CALL *VERIFY.SCHEMA(id,Fix,Brief,1)
CALL *VERIFY.SCHEMA(Slist<tmp>,Fix,Brief,1)
Slist = DELETE(Slist,tmp)
SPlist = DELETE(SPlist,tmp)
END
ELSE IF Verbose THEN CALL *WRAP.PRINT("* Neither '":id:"' nor '":Slist<tmp>:"' is a valid schema. Schema data for both should be deleted.",Width,0,2)
CONTINUE
END CASE
IF GetName = id
THEN
IF Fix
THEN
IF Verbose THEN CALL *WRAP.PRINT("* Schema '":Slist<tmp>:"' is not a valid schema. Deleting schema data for it.",Width,0,2)
CALL *VERIFY.SCHEMA(Slist<tmp>,Fix,Brief,1)
Slist<tmp> = id
END
ELSE IF Verbose THEN CALL *WRAP.PRINT("* Schema '":Slist<tmp>:"' is not a valid schema. It's schema data should be deleted.",Width,0,2)
END
ELSE IF GetName = Slist<tmp>
THEN
IF Fix
THEN
IF Verbose THEN CALL *WRAP.PRINT("* Schema '":id:"' is not a valid schema. Deleting schema data for it.",Width,0,2)
CALL *VERIFY.SCHEMA(id,Fix,Brief,1)
END
ELSE IF Verbose THEN CALL *WRAP.PRINT("* Schema '":id:"' is not a valid schema. It's schema data should be deleted.",Width,0,2)
END
ELSE
IF Fix
THEN
IF Verbose THEN CALL *WRAP.PRINT("* Neither '":id:"' nor '":Slist<tmp>:"' is the correct name for this schema. Deleting schema data for them both, and verifying data for '":GetName:"'.",Width,0,2)
CALL *VERIFY.SCHEMA(id,Fix,Brief,1)
CALL *VERIFY.SCHEMA(Slist<tmp>,Fix,Brief,1)
Slist = DELETE(Slist,tmp)
SPlist = DELETE(SPlist,tmp)
CALL *VERIFY.SCHEMA(SPlist<tmp>,Fix,Brief,1)
END
ELSE IF Verbose THEN CALL *WRAP.PRINT("* Neither '":id:"' nor '":Slist<tmp>:"' is the correct name for this schema. Schema data for them both should be deleted, and schema data for '":GetName:"' should be verified.",Width,0,2)
END
END
ELSE
SPlist = INSERT(SPlist,tmp;srec<2>)
Slist = INSERT(Slist,tmp;id)
END
REPEAT
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT("Checking UV_ASSOC for incorrect association information.",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
SSELECTV uvassoc TO listvar
done = 0
LOOP
READNEXT id FROM listvar ELSE done = 1
WHILE NOT(done) DO
READ trec FROM uvtables,id
THEN
key = id[1,INDEX(id,trec<3>,1)+LEN(trec<3>)-1]
assocname = id[INDEX(id,key,1)+LEN(key)+1,LEN(id)]
name = CONVERT(@TM,@FM,key)
READ atrec FROM uvtables,key
ELSE
ECount += 1
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT("* There is no Base Table which refers to the UV_TABLES association data for the association '":assocname:"' on table '":name<2>:" (":name<1>:")'.",Width,0,2)
IF Fix
THEN
IF Verbose THEN CALL *WRAP.PRINT("* Deleting SQL catalog data for association '":assocname:"'.",Width,0,2)
DELETE uvassoc,id
DELETE uvtables,id
END
ELSE IF Verbose THEN CALL *WRAP.PRINT("* SQL catalog data for association '":assocname:"' should be deleted.",Width,0,2)
END
CONTINUE
END
ELSE
ECount += 1
name = CONVERT(@TM,@FM,id)
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT("* No SQL catalog data for association '":name<2>:"' in UV_TABLES." ,Width,0,2)
IF Fix
THEN
IF Verbose THEN CALL *WRAP.PRINT("* Deleting SQL catalog data for association '":name<2>:"'.",Width,0,2)
DELETE uvassoc,id
END
ELSE IF Verbose THEN CALL *WRAP.PRINT("* SQL catalog data for association '":name<2>:"' should be deleted.",Width,0,2)
END
REPEAT
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT("Checking UV_VIEWS for incorrect view information.",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
SSELECTV uvview TO listvar
done = 0
LOOP
READNEXT id FROM listvar ELSE done = 1
WHILE NOT(done) DO
vname1 = CONVERT(@TM,".",id)
vname2 = CONVERT(@TM,@FM,id)
VwChange = 0
READ trec FROM uvtables,id
THEN
READ viewrec1 FROM uvview,id ELSE CONTINUE
* Rel 8 use " " as seperator *
* 9 use @VM as seperator *
IF COUNT(@VM, viewrec1<2>) >0 OR NOT (viewrec1<2> = "" OR viewrec1<2> = "no")
THEN
newremarks = CONVERT(@VM, @FM, viewrec1<2>)
remarks1 = CONVERT(@VM, @FM, viewrec1<2>)
END
ELSE
newremarks = CONVERT(" ", @FM, viewrec1<2>)
remarks1 = CONVERT(" ",@FM,viewrec1<2>)
END
FOR I = 1 to DCOUNT(remarks1,@FM)
** ONLY the first period is to be converted JBG 17337 **
remarks2 = remarks1<I>
dotsep = INDEX(remarks2, ".", 1)
remarks2[dotsep, 1] = @TM
READ tablerec1 FROM uvtables,remarks2
THEN
LOCATE(vname1,tablerec1,5;tmp)
THEN NULL
ELSE
ECount += 1
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Fix
THEN
LOCATE(remarks1<I>,newremarks;ttmp)
THEN
IF Verbose THEN CALL *WRAP.PRINT("* Deleting '":remarks1<I>:"' from (column Tables) for view '":vname2<2>:"' in UV_VIEWS." ,Width,0,2)
DEL newremarks<ttmp>
VwChange = 1
END
END
ELSE IF Verbose THEN CALL *WRAP.PRINT("* '":remarks1<I>:"' (column VIEWS) does not point to view '":vname2<2>:"'.",Width,0,2)
END
END
ELSE
ECount += 1
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Fix
THEN
LOCATE(remarks1<I>,newremarks;ttmp)
THEN
IF Verbose THEN CALL *WRAP.PRINT("* Deleting '":remarks1<I>:"' from (column Tables) for view '":vname2<2>:"' in UV_VIEWS." ,Width,0,2)
DEL newremarks<ttmp>
VwChange = 1
END
END
ELSE IF Verbose THEN CALL *WRAP.PRINT("* View '":vname2<2>:"' which references '":remarks1<I>:"' has no SQL catalog data in UV_TABLES." ,Width,0,2)
END
NEXT I
END
ELSE
ECount += 1
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
IF Verbose THEN CALL *WRAP.PRINT("* No SQL catalog data for view '":vname2<2>:"' in UV_TABLES." ,Width,0,2)
IF Fix
THEN
IF Verbose THEN CALL *WRAP.PRINT("* Deleting SQL catalog data for view '":vname2<2>:"'.",Width,0,2)
DELETE uvview,id
END
ELSE IF Verbose THEN CALL *WRAP.PRINT("* SQL catalog data for view '":vname2<2>:"' should be deleted.",Width,0,2)
END
IF VwChange AND Fix
THEN
viewrec1<2> = CONVERT(@FM,@VM, newremarks)
WRITE viewrec1 ON uvview,id
END
REPEAT
* End of main routine *
RETURN
***************************************************************************
*BOTTOM
***************************************************************************
GETUSER:
******************
** Windows NT port
**
UID = ICONV(CHKNAME, "PW")
IF STATUS() # 0 THEN UID = -1
**
******************
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
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
CALL *WRAP.PRINT("** Permission denied on table '":CHKNAME:"'.",Width,0,2)
EXVAL = 3
END
IF junk[1,18] = "Permission Denied." THEN
IF Verbose THEN CALL *WRAP.PRINT(" ",Width,0,0)
CALL *WRAP.PRINT("** Permission denied on table '":CHKNAME:"'.",Width,0,2)
EXVAL = 3
END
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 IsaView THEN
IF junk<1>[LEN(CHKNAME)+9,20] = ": View (UV type 41)."
THEN EXVAL = 2
END
RETURN
***************************************************************************
* This routine gets a SICA from an SQL file. We return the SICA in the *
* variable Sica or 0 if the is no sica in the file. *
***************************************************************************
GETSICA:
*******************************
* Get the SICA for the table. *
*******************************
SicaCMD = "LIST.SICA ":CHKNAME:" DATA"
EXECUTE SicaCMD CAPTURING Sica
********************************************************
* If there is a problem getting the SICA then Sica = 0 *
********************************************************
IF ((Sica[1,9] = "Unable to") OR (Sica[1,9] = "Could not") OR (Sica[20,9] = "Could not") OR (Sica[20,9] = "Unable to"))
THEN
Sica = 0
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[1,LEN(CHKNAME)-4]:"'.",Width,0,2)
GetName = -1
END
ELSE IF INDEX(junk,"Permission denied",1)
THEN
CALL *WRAP.PRINT("* Permission denied on schema '":CHKNAME[1,LEN(CHKNAME)-4]:"'.",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<DCOUNT(junk,@FM)>
IF GetName = "" THEN GetName = -3
END
END
RETURN
********************************************************************
* This routine is called when a table does not exist, but it still *
* has SQL catalog data. An easy way for this to happen if for *
* someone to create a table and then delete it with DELETE.FILE. *
********************************************************************
DELETE.DATA:
* tname = dynamic array of schema name and table name
* key = key for UV_TABLES data
* catrec = UV_TABLES catalog data
SQLDobject = 'table'
IF catrec<2> = "VIEW"
THEN
SQLDobject = 'view'
END
********************************************
* Delete the UV_TABLES data for the table. *
********************************************
IF Verbose THEN CALL *WRAP.PRINT("* Deleting table data for ":SQLDobject:" '":tname<2>:" (":tname<1>:")'.",Width,0,2)
DELETE uvtables,key
**********************************************
* Delete the UV_COLUMNS data for this table. *
**********************************************
IF Verbose THEN CALL *WRAP.PRINT("* Deleting column data for ":SQLDobject:" '":tname<2>:" (":tname<1>:")'.",Width,0,2)
FOR I = 1 to DCOUNT(catrec<4>, @VM)
DELETE uvcolumns,key:@TM:catrec<4,I>
NEXT I
**********************************************
* Delete the association data for this file. *
* This is both UV_TABLES and UV_ASSOC data. *
**********************************************
IF Verbose THEN CALL *WRAP.PRINT("* Deleting association data for ":SQLDobject:" '":tname<2>:" (":tname<1>:")'.",Width,0,2)
FOR I = 1 to DCOUNT(catrec<8>, @VM)
DELETE uvtables,key:"_":catrec<8,I>
DELETE uvassoc,key:"_":catrec<8,I>
NEXT I
**********************************************
* Delete the view data for this file. *
* This is both UV_TABLES column VIEWS *
* and UV_VIEWS *
**********************************************
IF catrec<2> = "VIEW"
THEN
READ viewrec FROM uvview,key
THEN
IF COUNT(@VM, viewrec<2>) > 0 OR NOT (viewrec<2> = "" OR viewrec<2> = "no")
THEN remarks = CONVERT(@VM,@FM,viewrec<2>)
ELSE remarks = CONVERT(" ",@FM,viewrec<2>)
vname = CONVERT(@TM,".",key)
FOR I = 1 to DCOUNT(remarks,@FM)
** convert only the FIRST period to @TM **
remarks = remarks1<I>
dotsep = INDEX(remarks, ".", 1)
remarks[dotsep, 1] = @TM
READ tablerec FROM uvtables,remarks
THEN
LOCATE(vname,tablerec,5;tmp)
THEN
IF Verbose THEN CALL *WRAP.PRINT("* Deleting table data (column VIEWS) for view '":tname<2>:" (":tname<1>:")'.",Width,0,2)
DEL tablerec<5,tmp>
WRITE tablerec ON uvtables,remarks
END
END
NEXT I
END
IF Verbose THEN CALL *WRAP.PRINT("* Deleting view data for view '":tname<2>:" (":tname<1>:")'.",Width,0,2)
DELETE uvview,key
END
******************************************************
* Delete all UV_USERS ownership data for this table. *
******************************************************
EXECUTE "SELECT UV_USERS WITH SCHEMAS LIKE ...":tname<1>:"..." RTNLIST rlst CAPTURING junk
SavRec = 0
loopa:
READNEXT uid FROM rlst ELSE GOTO loopb
READ delrec FROM uvusers,uid ELSE GOTO loopa
CNT = 1
BOUNDS = DCOUNT(delrec<5>,@VM)
LOOP WHILE CNT <= BOUNDS DO
IF delrec<5,CNT> = tname<2> AND delrec<4,CNT> = tname<1>
THEN
IF Verbose THEN CALL *WRAP.PRINT("* Deleting ownership record for user '":uid:"'.",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,uid ELSE CALL *WRAP.PRINT("* Problems with the write. Unable to delete ownership record for user '":uid:"'.",Width,5,0)
SavRec = 0
END
GOTO loopa
loopb:
*******************************************************
* Delete all UV_USERS permission data for this table. *
*******************************************************
EXECUTE "SELECT UV_USERS WITH PERM_SCHEMAS LIKE ...":tname<1>:"..." RTNLIST rlst CAPTURING junk
loopc:
READNEXT uid FROM rlst ELSE GOTO loopd
READ delrec FROM uvusers,uid ELSE GOTO loopc
BOUNDS = DCOUNT(delrec<7>,@VM)
CNT = 1
LOOP WHILE CNT <= BOUNDS DO
IF delrec<7,CNT> = trec<2> AND delrec<6,CNT> = trec<1>
THEN
IF Verbose THEN CALL *WRAP.PRINT("* Deleting permission record for user '":uid:"'.",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,uid ELSE CALL *WRAP.PRINT("* Problems with the write. Unable to delete permission record for user '":uid:"'.",Width,0,2)
SavRec = 0
END
GOTO loopc
loopd:
RETURN
END