DatabaseProcApplicationCreatedLinks
sybsystemprocssp_modifystats  31 Aug 14Defects Dependencies

1     
2     
3     /*
4     ** Messages for "sp_modifystats"
5     ** 17460, "Object must be in the current database."
6     ** 17563, "The table does not have a column named '%1!'."
7     ** 18118, "Object '%1!' does not exist in this database."
8     ** 18162, "'%1!' is a not a user table. '%2!' can be used only on user tables."
9     ** 18884, "No statistics exist for column '%1!'."
10    ** 18921, "Unable to execute stored procedure '%1!'.This version of the procedure is based on a '%2!' byte column ID and is incompatible with the server's column ID size.
11    ** 18922, "Command failed. The 'value' argument for 'MODIFY_DENSITY' must be greater than or equal to 0.0 and not more than 1.0 when the 'absolute' method is specified.
12    ** 18923, "The density value of column group '%1!' exceeded 1.0 and has been set to 1.0. Processing continues.
13    ** 19569, "UPDATE STATISTICS permission denied on object '%1!'."
14    */
15    
16    /*
17    ** IMPORTANT NOTE:
18    ** This stored procedure uses the built-in function object_id() in the
19    ** where clause of a select query. If you intend to change this query
20    ** or use the object_id() or db_id() builtin in this procedure, please read the
21    ** READ.ME file in the $DBMS/generic/sproc directory to ensure that the rules
22    ** pertaining to object-id's and db-id's outlined there, are followed.
23    */
24    
25    create procedure sp_modifystats
26        @objname varchar(767) = null, /* user table name */
27        @column_group varchar(1200) = null, /* column name */
28        @option varchar(60) = null, /* statistic to be modified */
29        @opt_param1 varchar(255) = null, /* optional param */
30        @opt_param2 varchar(255) = null, /* optional param */
31        @opt_param3 varchar(255) = null /* optional param */
32    as
33        /*
34        **
35        **	Description: Allow sa to modify statistics stored
36        **				in sysstatistics.
37        **
38        **	Argument:	all uses of sp_modifystats require at least
39        **			three arguments: the table in question;
40        **			the column or column group (note that this
41        **			can be null); and the option.  Since different
42        **			options may require different arguments,several
43        **			@opt_param varchar(255) args are provided.
44        **			Please do not modify the datatype of these
45        **			params,	rather use the convert function within
46        **			your option.
47        **			Additional @opt_param parameters may be added
48        **			as they are needed.
49        **
50        **	Options:	"REMOVE_SKEW_FROM_DENSITY"  -
51        **				This option allows sa to change the
52        **				total density of a column to be equal
53        **				to the range density which is useful
54        **				when data skew is present.
55        **				This will also update the total density of
56        **				any composite column statistics for which
57        **				this column is the leading attribute.
58        **				Most commonly, a composite index for which
59        **				this column is the leading attribute would
60        **				produce such composite column statistics,
61        **				but they can also be produced by a
62        **				composite update column statistics such as
63        **				update statistics t1(a,b,c) 
64        **				REQUIRES @objname, @column_group, @option.
65        **
66        **			"MODIFY_DENSITY" -
67        **				This option provides a very granular
68        **				mechanism to modify either the range or
69        **				total density for a column or column
70        **				group.
71        **				Explanation of syntax:
72        **				"[database].[owner].table" -
73        **					object name you wish to modify
74        **				{ "column_group" | "all" } - the column
75        **					or groups of columns to modify.
76        **				Rules: "all" will modify all columns
77        **						for this table
78        **					"a1" will modify column a1
79        **					"a1,a2,a3" will
80        **						modify the group a1,a2,a3
81        **					"a1,%,a3" will modify
82        **						the groups a1,a2,a3 and 
83        **						a1,a5,a3, etc.
84        **					"a1,%" will modify
85        **						the groups a1,a2
86        **						and a1,a2,a3, etc. but
87        **						not a1.
88        **					"a1%" will modify
89        **						the groups a1,a2 and
90        **						a1,a2,a3 AS WELL AS a1.
91        **				{ range | total } - modify either
92        **					range cell or total cell density
93        **				{ absolute | factor } - type of
94        **					modification to do. If absolute,
95        **					then the value argument is the
96        **					value you want.  If factor, then
97        **					multiply existing value by the
98        **					value argument
99        **				value - the target value.  Must be >= 0
100       **					and <= 1.0 if absolute is
101       **					specified
102       **				REQUIRES @objname,@column_group, @option,
103       **					@opt_param1, @opt_param2,
104       **					@opt_param3
105       **
106       **
107       **	Future Info:	Other options can be added in the future
108       **				using the @option parameter.
109       **
110       **	Dependencies:	This proc relies on the object_id built-in,
111       **			and the db_name() built-in. Additionally,
112       **			it must be created with updates to system
113       **			tables enabled.
114       **
115       **	Errors:		This proc relies on the following errors:
116       **				17460, 17563, 18118, 18162
117       **			Errors 18884, 18921, 18922, 18923
118       **				are installed for this proc.
119       **
120       **	Version:	This proc is for ASE 11.9.x and beyond
121       **
122       **	Usage:		sp_modifystats tabname, column_group, opt
123       **
124       **	History:	9/16/99	(mciccone)
125       **			2/1/01	(dwein - changed structure of proc
126       **					to improve modularization)
127       **			2/1/01	(dwein - added MODIFY_DENSITY)
128       */
129   
130       /*
131       ** Note that any local variables needed for your module
132       ** should be declared within that module only.  @rows,
133       ** @err, and @colid are retained here to encourage their use.
134       */
135   
136       declare @rows int /* Variable to check @@rowcount */
137       declare @err int /* Variable to check @@error */
138       declare @colid int /* Variable to hold colid from syscolumns */
139       declare @colidsize int /* Variable to hold colid size for the server */
140       declare @role_name varchar(30) /* Stores role name */
141       declare @user_role_per int /* Variable to indicate whether user has
142       ** permission to execute the procedure
143       ** through any role
144       */
145   
146       set nocount on
147   
148       /*
149       ** Check colid size to avoid executing this proc
150       ** on a server with different colid size.
151       */
152       select @colidsize = length from syscolumns
153       where id = object_id("syscolumns") and name = "colid"
154   
155       if (@colidsize != 2)
156       begin
157           /*
158           ** 18921, "Unable to execute stored procedure '%1!'.This version of the
159           ** procedure is based on a '%2!' byte column ID and is incompatible 
160           ** with the server's column ID size."
161           */
162           raiserror 18921, "sp_modifystats", "2"
163           return (1)
164       end
165   
166       /* Check Usage */
167   
168       /*
169       ** Note that when adding modules to this procedure they must
170       ** be added to this check.
171       */
172   
173       if (@objname is null) or (@option not in (
174                   "REMOVE_SKEW_FROM_DENSITY",
175                   "MODIFY_DENSITY"))
176       begin
177           /*
178           ** When adding an option, be sure to add it to this usage
179           ** output.
180           */
181           print "Usage: sp_modifystats objname, column_group, option"
182           print "Valid Options:"
183           print "REMOVE_SKEW_FROM_DENSITY,"
184           print "MODIFY_DENSITY"
185           return (1)
186       end
187   
188       /* Only operate on tables in current database */
189       if @objname like "%.%.%" and
190           substring(@objname, 1, charindex(".", @objname) - 1) != db_name()
191       begin
192           /* 17460, "Object must be in the current database." */
193           raiserror 17460
194           return (1)
195       end
196   
197       /* Check to see if the @objname is in sysobjects. */
198       if not exists (select * from sysobjects
199               where id = object_id(@objname))
200       begin
201           /* 18118, "Object '%1!' does not exist in this database." */
202           raiserror 18118, @objname
203           return (1)
204       end
205   
206       /*
207       ** Make sure @objname in NOT a system table.
208       ** Check status bit within sysobjects.systats. This is same
209       ** method the server uses internally to determine if an object
210       ** is a system table.
211       */
212       if ((select (sysstat & 15) from sysobjects where
213                       id = object_id(@objname)) = 1)
214       begin
215           /*
216           ** 18162: '%1!' is a not a user table.
217           ** '%2!' can be used only on user tables.
218           */
219           raiserror 18162, @objname, "sp_modifystats"
220           return (1)
221       end
222   
223       /*
224       ** Check for UPDATE STATISTICS permission on object.
225       ** Will have to check for groups and roles that the user belongs to.
226       */
227   
228       /*
229       ** Initialise @user_role_per to 0, indicating user does not have permission
230       ** for UPDATE STATISTICS through any user defined roles or contained roles
231       */
232       select @user_role_per = 0
233   
234       declare role_name cursor for
235       select srvro.name from sysprotects p1,
236           master.dbo.syssrvroles srvro,
237           sysroles ro
238       where p1.id = object_id(@objname)
239           and p1.uid = ro.lrid
240           and ro.id = srvro.srid
241           and p1.action = 326
242       for read only
243   
244       open role_name
245   
246       fetch role_name into @role_name
247       while (@@sqlstatus = 0 and @user_role_per != 1)
248       begin
249           if @role_name is not null
250           begin
251               if (has_role(@role_name, 1) > 0)
252               begin
253                   /*
254                   ** User has role which has
255                   ** permission for UPDATE STATISTICS
256                   */
257                   select @user_role_per = 1
258               end
259           end
260           fetch role_name into @role_name
261       end
262       close role_name
263       deallocate cursor role_name
264   
265       /* 
266       ** If user has sa_role, then has UPDATE STATISTICS 
267       ** permission on the object 
268       */
269       if ((charindex("sa_role", show_role()) = 0)
270   
271               /*
272               ** If user is the owner of the object, then has UPDATE STATISTICS permission
273               ** on the object
274               */
275               and not exists (select id from sysobjects
276                   where id = object_id(@objname)
277                       and uid = user_id())
278   
279               and ((select max((abs(p.uid - u2.gid) * 2) +
280                   ((p.protecttype / 2) ^ 1))
281                   from sysprotects p, sysusers u2
282                   where p.id = object_id(@objname)
283                       and u2.uid = user_id()
284   
285                       /* get rows for public, current users, user's groups */
286                       and (p.uid = 0 /* get rows for public */
287                           or p.uid = user_id() /* current user */
288                           or p.uid = u2.gid) /* users group */
289                       and (p.action in (326)) /* check for UPDATE STATISTICS privilege */
290                   ) & 1) is NULL
291   
292               /*
293               ** If @user_role_per = 0, then user doesnot have permission through any 
294               ** user defined roles or contained roles 
295               */
296               and @user_role_per = 0)
297       begin
298           /* 19569, "UPDATE STATISTICS permission denied on object '%1!'." */
299           raiserror 19569, @objname
300           return (1)
301       end
302   
303       if @@trancount = 0
304       begin
305           set chained off
306       end
307   
308       set transaction isolation level 1
309       if @option = "REMOVE_SKEW_FROM_DENSITY"
310       /**Update total density for specified column**/
311       begin
312   
313           /*
314           ** The first action of any module is to setup
315           ** module specific variables and validate
316           ** any module-specific usage.
317           */
318   
319           /* Validate @columngroup value, as it is required by this module */
320           /* Step 1 : make sure it isn't null */
321           if (@column_group is null)
322           begin
323               print "Usage for REMOVE_SKEW_FROM_DENSITY option:"
324               print "sp_modifystats table_name, column_name, REMOVE_SKEW_FROM_DENSITY"
325               return (1)
326           end
327           /* Step 2: Check to see if the @column_group is in syscolumns */
328           if not exists (select * from syscolumns
329                   where id = object_id(@objname) and name = @column_group)
330           begin
331               /* 17563: "The table does not have a column named '%1!'." */
332               raiserror 17563, @column_group
333               return (1)
334           end
335   
336           /* We are ready to proceed with the actual work. */
337           select @colid = (select colid from syscolumns
338                   where id = object_id(@objname) and name = @column_group)
339           begin tran
340           /*
341           ** Change the total density & update STATISTICS_EDITED flag
342           */
343           update sysstatistics set c3 = c2,
344               c1 = convert(varbinary, (convert(int, c1) | 2))
345           where convert(smallint, substring(colidarray, 1, 2)) = @colid
346               and id = object_id(@objname)
347               and formatid = 100
348   
349           select @rows = @@rowcount, @err = @@error
350           if @err != 0
351           begin
352               select @err
353               rollback tran
354               return (1)
355           end
356           if @rows >= 1
357           begin
358               /* Successful update */
359               commit tran
360               return (0)
361           end
362           else
363           begin
364               /* 18884: No statistics exist for column '%1!'. */
365               raiserror 18884, @column_group
366               rollback tran
367               return (1)
368           end
369       end
370       /* end of REMOVE_SKEW_FROM_DATA module */
371   
372       else if (@option = "MODIFY_DENSITY")
373       /* granular modification of density values */
374       begin
375   
376           /*
377           ** The first action of any module is to setup
378           ** module specific variables and to validate
379           ** any module-specific usage.
380           */
381   
382           /* declare values local to this module */
383           declare @density_type varchar(5) /* @opt_param1 */
384           declare @method varchar(8) /* @opt_param2 */
385           declare @target_value double precision /* @opt_param3 */
386           declare @col_count int, @col_length int
387           declare @col_position int, @position int
388           declare @colidarray varbinary(100)
389           declare @indid smallint
390           declare @partitionid int
391           declare @column_name varchar(255)
392           declare @column_string varchar(1200)
393   
394           /* assign @opt_param values to semantically approriate values */
395           select @density_type = @opt_param1, @method = @opt_param2,
396               @target_value = convert(double precision, @opt_param3)
397   
398           /* Validate arguments*/
399           if (@column_group is null) or (@density_type not in ("range", "total"))
400               or (@method not in ("absolute", "factor"))
401               or (@target_value is null)
402           begin
403               print "Usage for MODIFY_DENSITY option:"
404               print "sp_modifystats ""[database].[owner].table"", { ""column_group"" | ""all"" },"
405               print "  MODIFY_DENSITY, { range | total }, {absolute | factor}, ""value"" "
406               return (1)
407           end
408   
409           /* Make sure our value isn't bogus */
410           if (@target_value < 0) or (@target_value > 1.0 and @method = "absolute")
411           begin
412               /*
413               ** 18922, "Command failed. The 'value' argument for 
414               ** 'MODIFY_DENSITY' must be greater than or equal to 0.0 and
415               ** not more than 1.0 when the 'absolute' method is specified."
416               */
417               raiserror 18922
418               return (1)
419           end
420   
421           /* Go through the column list looking for valid columns */
422           if @column_group != "all"
423           begin
424               select @col_length = char_length(@column_group)
425               select @position = 1
426               select @col_count = 0
427   
428               /* Eliminate possible white spaces introduced by user */
429               select @position = charindex(" ", @column_group)
430               while (@position != 0)
431               begin
432                   select @column_group =
433                       stuff(@column_group, @position, 1, null)
434                   select @position = charindex(" ", @column_group)
435               end
436   
437               /* Eliminate possible tab chars introduced by user */
438               select @position = charindex(char(9), @column_group)
439               while (@position != 0)
440               begin
441                   select @column_group =
442                       stuff(@column_group, @position, 1, null)
443                   select @position = charindex(char(9), @column_group)
444               end
445   
446               select @position = 1
447               select @col_length = char_length(@column_group)
448   
449               /*
450               ** We must loop through @column_group to find the column names.
451               ** @position is used in the outer loop, and marks the character
452               ** position within @column_group.  @col_position is used in
453               ** the inner loop and marks the number of characters FROM @position
454               ** until we hit either the end of the string or a comma.
455               */
456               while (@position <= @col_length)
457               begin
458                   select @col_position = 0
459                   while ((substring(@column_group,
460                                   (@position + @col_position), 1) != ",") and
461                           ((@position + @col_position) <= @col_length))
462                   begin
463                       select @col_position = @col_position + 1
464                   end
465   
466                   /* Check for wildcards */
467                   if (substring(@column_group, @position, @col_position) != "%")
468                   begin
469                       /* 
470                       ** Our column is not a wildcard, so make sure 
471                       ** it exits
472                       */
473                       if not exists (select colid from syscolumns
474                               where id = object_id(@objname)
475                                   and name like substring(@column_group,
476                                       @position, @col_position))
477                       begin
478                           select @column_name = substring(@column_group,
479                                   @position, @col_position)
480                           /*
481                           ** 17563: "The table does not have a
482                           ** column named '%1!'."
483                           */
484                           raiserror 17563, @column_name
485                           return (1)
486                       end
487                   end
488                   select @position = @position + @col_position + 1
489                   select @col_count = @col_count + 1
490               end
491           end /* column validation end */
492   
493           /* Create a #table to hold the old and new values */
494           create table #densities(indid smallint, partitionid int,
495               colidarray varbinary(100),
496               column_string varchar(1200) null,
497               density_type char(5),
498               old_value double precision,
499               new_value double precision null)
500   
501           /* Create an index to aid in cursor processing */
502           create unique clustered index densities_CI on
503           #densities(indid, partitionid, colidarray)
504   
505           /*
506           ** Insert into #densities all formatid 100 rows for the object
507           ** we note the old value and set the new value to @target_value
508           */
509           insert #densities select indid, partitionid, colidarray, null,
510               @density_type,
511               case
512                   when @density_type = "range" then convert(double precision, c2)
513                   when @density_type = "total" then convert(double precision, c3)
514               end
515               , @target_value
516           from sysstatistics where formatid = 100 and id = object_id(@objname)
517   
518           /* If we are using factoring, correct the new value */
519           if @method = "factor"
520               update #densities set new_value = (old_value * @target_value)
521   
522           /* We now need to cursor through #densities and rebuild  column string */
523           declare new_densities cursor for
524           select indid, partitionid, colidarray
525           from #densities for update
526   
527           open new_densities
528           fetch new_densities into @indid, @partitionid, @colidarray
529           select @column_string = ""
530           while (@@sqlstatus = 0)
531           begin
532               select @position = 1
533               select @col_length = char_length(@colidarray)
534               /* Build the column list string */
535               while (convert(smallint, substring(@colidarray, @position, 2)) != 0)
536                   and (@position <= @col_length)
537               begin
538                   select @colid = convert(smallint,
539                       substring(@colidarray, @position, 2))
540                   if @position != 1
541                       select @column_string = @column_string + ","
542                   select @column_string = @column_string +
543                           (select name from syscolumns where
544                               id = object_id(@objname) and
545                               colid = @colid)
546                   select @position = @position + 2
547               end
548   
549               /* Now update the #table with the string */
550               update #densities set column_string =
551                   ltrim(rtrim(@column_string))
552               where colidarray = @colidarray
553                   and indid = @indid
554                   and partitionid = @partitionid
555   
556               /* Get rid of the row if we don't want it */
557               if @column_group != "all"
558                   delete #densities
559                   where column_string not like @column_group
560                       and colidarray = @colidarray
561                       and indid = @indid
562                       and partitionid = @partitionid
563   
564               /* Check to see it our row stills exists */
565               if exists (select * from #densities
566                       where colidarray = @colidarray
567                           and indid = @indid
568                           and partitionid = @partitionid)
569               begin
570                   /*
571                   ** Now check to see if we have gone over 1.0 for
572                   ** a density
573                   */
574                   if (select new_value from #densities
575                           where colidarray = @colidarray
576                               and indid = @indid
577                               and partitionid = @partitionid) > 1.0
578                   begin
579                       /* 
580                       ** 18923, "The density value of column group 
581                       ** '%1!' exceeded 1.0 and has been set to 1.0.
582                       ** Processing continues."
583                       */
584                       raiserror 18923, @column_string
585   
586                       update #densities
587                       set new_value = 1.0
588                       where colidarray = @colidarray
589                           and indid = @indid
590                           and partitionid = @partitionid
591                   end
592               end
593               select @column_string = ""
594               fetch new_densities into @indid, @partitionid, @colidarray
595           end
596   
597           close new_densities
598           deallocate cursor new_densities
599   
600           /*
601           ** We can now set sysstatistics appropriately
602           ** Notice that c1 is or'd with 2, as this sets the stats edited flag
603           */
604           begin transaction
605   
606           if (@density_type = "range")
607           begin
608               update sysstatistics set c2 = convert(varbinary(255), new_value),
609                   c1 = convert(varbinary, (convert(int, c1) | 2))
610               from #densities where
611                   sysstatistics.colidarray = #densities.colidarray
612                   and formatid = 100 and id = object_id(@objname)
613                   and sysstatistics.indid = #densities.indid
614                   and sysstatistics.partitionid = sysstatistics.partitionid
615           end
616           else
617           begin /* Setting total density in this case */
618               update sysstatistics set c3 = convert(varbinary(255), new_value),
619                   c1 = convert(varbinary, (convert(int, c1) | 2))
620               from #densities where
621                   sysstatistics.colidarray = #densities.colidarray
622                   and formatid = 100 and id = object_id(@objname)
623                   and sysstatistics.indid = #densities.indid
624                   and sysstatistics.partitionid = sysstatistics.partitionid
625           end
626   
627           /* Do some error checking */
628           select @rows = @@rowcount, @err = @@error
629           if @err != 0
630           begin
631               select @err
632               rollback tran
633               return (1)
634           end
635           if @rows >= 1
636           begin
637               /* Successful update */
638               commit tran
639           end
640           else
641           begin
642               /* 18884: No statistics exist for column '%1!'. */
643               raiserror 18884, @column_group
644               rollback tran
645               return (1)
646           end
647   
648           /*
649           ** Now display the output.  Pull new values from
650           ** sysstatistics for accuracy purposes
651           */
652   
653           select "Densities updated for table " + @objname + " by SP_MODIFYSTATS"
654   
655           select d.column_string "Column Group",
656               d.density_type "Density Type",
657               convert(decimal(9, 8), d.old_value) "Original Value",
658               case
659                   when @density_type = "range" then
660                   convert(decimal(9, 8),
661                   convert(double precision, s.c2))
662                   when @density_type = "total" then
663                   convert(decimal(9, 8),
664                   convert(double precision, s.c3))
665               end "New Value"
666           from sysstatistics s, #densities d where
667               s.formatid = 100 and s.id = object_id(@objname) and
668               s.colidarray = d.colidarray
669   
670           /* We are all done! */
671           return (0)
672   
673       end
674   


exec sp_procxmode 'sp_modifystats', 'AnyMode'
go
RESULT SETS
sp_modifystats_rset_004
sp_modifystats_rset_003
sp_modifystats_rset_002
sp_modifystats_rset_001

DEFECTS
 MCTR 4 Conditional Begin Tran or Commit Tran 339
 MCTR 4 Conditional Begin Tran or Commit Tran 359
 MCTR 4 Conditional Begin Tran or Commit Tran 604
 MCTR 4 Conditional Begin Tran or Commit Tran 638
 MEST 4 Empty String will be replaced by Single Space 529
 MEST 4 Empty String will be replaced by Single Space 593
 MINU 4 Unique Index with nullable columns sybsystemprocs..sysprotects sybsystemprocs..sysprotects
 MINU 4 Unique Index with nullable columns sybsystemprocs..sysstatistics sybsystemprocs..sysstatistics
 MTYP 4 Assignment type mismatch @density_type: varchar(5) = varchar(255) 395
 MTYP 4 Assignment type mismatch @method: varchar(8) = varchar(255) 395
 QPUI 4 Join or Sarg with Un-Rooted Partial Index Use JOIN Candidate index: sysprotects.csysprotects unique clustered
(id, action, grantor, uid, protecttype)
Intersection: {uid}
Uncovered: [grantor, protecttype]
288
 QTYP 4 Comparison type mismatch Comparison type mismatch: smallint vs int 241
 QTYP 4 Comparison type mismatch smallint = int 345
 QTYP 4 Comparison type mismatch Comparison type mismatch: tinyint vs int 347
 QTYP 4 Comparison type mismatch Comparison type mismatch: tinyint vs int 516
 QTYP 4 Comparison type mismatch Comparison type mismatch: smallint vs int 545
 QTYP 4 Comparison type mismatch smallint = int 545
 QTYP 4 Comparison type mismatch Comparison type mismatch: tinyint vs int 612
 QTYP 4 Comparison type mismatch Comparison type mismatch: tinyint vs int 622
 QTYP 4 Comparison type mismatch Comparison type mismatch: tinyint vs int 667
 CUSU 3 Cursor updated through 'searched update': risk of halloween rows new_densities 550
 CUSU 3 Cursor updated through 'searched update': risk of halloween rows new_densities 558
 CUSU 3 Cursor updated through 'searched update': risk of halloween rows new_densities 586
 MGTP 3 Grant to public master..syssrvroles  
 MGTP 3 Grant to public sybsystemprocs..syscolumns  
 MGTP 3 Grant to public sybsystemprocs..sysobjects  
 MGTP 3 Grant to public sybsystemprocs..sysprotects  
 MGTP 3 Grant to public sybsystemprocs..sysroles  
 MGTP 3 Grant to public sybsystemprocs..sysstatistics  
 MGTP 3 Grant to public sybsystemprocs..sysusers  
 MNER 3 No Error Check should check @@error after insert 509
 MNER 3 No Error Check should check @@error after update 520
 MNER 3 No Error Check should check @@error after update 550
 MNER 3 No Error Check should check @@error after delete 558
 MNER 3 No Error Check should check @@error after update 586
 MNER 3 No Error Check should check @@error after update 608
 MNER 3 No Error Check should check @@error after update 618
 MUCO 3 Useless Code Useless Brackets 155
 MUCO 3 Useless Code Useless Brackets 163
 MUCO 3 Useless Code Useless Brackets 185
 MUCO 3 Useless Code Useless Brackets 194
 MUCO 3 Useless Code Useless Brackets 203
 MUCO 3 Useless Code Useless Brackets 212
 MUCO 3 Useless Code Useless Brackets 220
 MUCO 3 Useless Code Useless Brackets 247
 MUCO 3 Useless Code Useless Brackets 251
 MUCO 3 Useless Code Useless Brackets 269
 MUCO 3 Useless Code Useless Brackets 279
 MUCO 3 Useless Code Useless Brackets 280
 MUCO 3 Useless Code Useless Brackets 300
 MUCO 3 Useless Code Useless Brackets 321
 MUCO 3 Useless Code Useless Brackets 325
 MUCO 3 Useless Code Useless Brackets 333
 MUCO 3 Useless Code Useless Brackets 354
 MUCO 3 Useless Code Useless Brackets 360
 MUCO 3 Useless Code Useless Brackets 367
 MUCO 3 Useless Code Useless Brackets 372
 MUCO 3 Useless Code Useless Brackets 406
 MUCO 3 Useless Code Useless Brackets 418
 MUCO 3 Useless Code Useless Brackets 430
 MUCO 3 Useless Code Useless Brackets 439
 MUCO 3 Useless Code Useless Brackets 456
 MUCO 3 Useless Code Useless Brackets 459
 MUCO 3 Useless Code Useless Brackets 467
 MUCO 3 Useless Code Useless Brackets 485
 MUCO 3 Useless Code Useless Brackets 520
 MUCO 3 Useless Code Useless Brackets 530
 MUCO 3 Useless Code Useless Brackets 606
 MUCO 3 Useless Code Useless Brackets 633
 MUCO 3 Useless Code Useless Brackets 645
 MUCO 3 Useless Code Useless Brackets 671
 MUIN 3 Column created using implicit nullability 494
 QAFM 3 Var Assignment from potentially many rows 152
 QCRS 3 Conditional Result Set 352
 QCRS 3 Conditional Result Set 631
 QCRS 3 Conditional Result Set 653
 QCRS 3 Conditional Result Set 655
 QCTC 3 Conditional Table Creation 494
 QISO 3 Set isolation level 308
 QJWT 3 Join or Sarg Without Index on temp table 611
 QJWT 3 Join or Sarg Without Index on temp table 621
 QJWT 3 Join or Sarg Without Index on temp table 668
 QNAJ 3 Not using ANSI Inner Join 235
 QNAJ 3 Not using ANSI Inner Join 281
 QNAJ 3 Not using ANSI Inner Join 666
 QNAM 3 Select expression has no name @err 352
 QNAM 3 Select expression has no name @err 631
 QNAM 3 Select expression has no name "Densities updated for table " + @objname + " by SP_MODIFYSTATS" 653
 QNUA 3 Should use Alias: Column new_value should use alias #densities 608
 QNUA 3 Should use Alias: Column c1 should use alias sysstatistics 609
 QNUA 3 Should use Alias: Table #densities 610
 QNUA 3 Should use Alias: Column formatid should use alias sysstatistics 612
 QNUA 3 Should use Alias: Column id should use alias sysstatistics 612
 QNUA 3 Should use Alias: Column new_value should use alias #densities 618
 QNUA 3 Should use Alias: Column c1 should use alias sysstatistics 619
 QNUA 3 Should use Alias: Table #densities 620
 QNUA 3 Should use Alias: Column formatid should use alias sysstatistics 622
 QNUA 3 Should use Alias: Column id should use alias sysstatistics 622
 QPRI 3 Join or Sarg with Rooted Partial Index Use SARG Candidate index: syscolumns.csyscolumns unique clustered
(id, number, colid)
Intersection: {id}
153
 QPRI 3 Join or Sarg with Rooted Partial Index Use SARG Candidate index: sysprotects.csysprotects unique clustered
(id, action, grantor, uid, protecttype)
Intersection: {action, id}
238
 QPRI 3 Join or Sarg with Rooted Partial Index Use SARG Candidate index: syscolumns.csyscolumns unique clustered
(id, number, colid)
Intersection: {id}
329
 QPRI 3 Join or Sarg with Rooted Partial Index Use SARG Candidate index: syscolumns.csyscolumns unique clustered
(id, number, colid)
Intersection: {id}
338
 QPRI 3 Join or Sarg with Rooted Partial Index Use SARG Candidate index: sysstatistics.csysstatistics unique clustered
(id, indid, partitionid, statid, colidarray, formatid, sequence)
Intersection: {colidarray, id, formatid}
345
 QPRI 3 Join or Sarg with Rooted Partial Index Use SARG Candidate index: syscolumns.csyscolumns unique clustered
(id, number, colid)
Intersection: {id}
474
 QPRI 3 Join or Sarg with Rooted Partial Index Use SARG Candidate index: sysstatistics.csysstatistics unique clustered
(id, indid, partitionid, statid, colidarray, formatid, sequence)
Intersection: {formatid, id}
516
 QPRI 3 Join or Sarg with Rooted Partial Index Use SARG Candidate index: syscolumns.csyscolumns unique clustered
(id, number, colid)
Intersection: {colid, id}
544
 QPRI 3 Join or Sarg with Rooted Partial Index Use SARG Candidate index: sysstatistics.csysstatistics unique clustered
(id, indid, partitionid, statid, colidarray, formatid, sequence)
Intersection: {formatid, id}
612
 QPRI 3 Join or Sarg with Rooted Partial Index Use SARG Candidate index: sysstatistics.csysstatistics unique clustered
(id, indid, partitionid, statid, colidarray, formatid, sequence)
Intersection: {formatid, id}
622
 QPRI 3 Join or Sarg with Rooted Partial Index Use SARG Candidate index: sysstatistics.csysstatistics unique clustered
(id, indid, partitionid, statid, colidarray, formatid, sequence)
Intersection: {formatid, id}
667
 QPSC 3 Join on same column sysstatistics.partitionid 614
 QPSC 3 Join on same column sysstatistics.partitionid 624
 CRDO 2 Read Only Cursor Marker (has for read only clause) 235
 CUPD 2 Updatable Cursor Marker (has for update clause) 524
 MRST 2 Result Set Marker 352
 MRST 2 Result Set Marker 631
 MRST 2 Result Set Marker 653
 MRST 2 Result Set Marker 655
 MSUB 2 Subquery Marker 198
 MSUB 2 Subquery Marker 212
 MSUB 2 Subquery Marker 275
 MSUB 2 Subquery Marker 279
 MSUB 2 Subquery Marker 328
 MSUB 2 Subquery Marker 337
 MSUB 2 Subquery Marker 473
 MSUB 2 Subquery Marker 543
 MSUB 2 Subquery Marker 565
 MSUB 2 Subquery Marker 574
 MTR1 2 Metrics: Comments Ratio Comments: 48% 25
 MTR2 2 Metrics: Cyclomatic Complexity Cyclo: 50 = 66dec - 18exi + 2 25
 MTR3 2 Metrics: Query Complexity Complexity: 297 25
 PRED_QUERY_COLLECTION 2 {p=sybsystemprocs..sysprotects, r=sybsystemprocs..sysroles, s=master..syssrvroles} 0 235
 PRED_QUERY_COLLECTION 2 {p=sybsystemprocs..sysprotects, u=sybsystemprocs..sysusers} 0 279

DEPENDENCIES
PROCS AND TABLES USED
read_writes table sybsystemprocs..sysstatistics  
reads table sybsystemprocs..sysprotects  
reads table master..syssrvroles (1)  
reads table sybsystemprocs..sysusers  
reads table sybsystemprocs..syscolumns  
reads table sybsystemprocs..sysroles  
read_writes table tempdb..#densities (1) 
reads table sybsystemprocs..sysobjects