zOs/SQL/QM416204

--$SPECIAL
select current timestamp "timestamp",
       current member "member", current server "server",
               '11.9.13 alte queries' "version"
    from sysibm.sysDummy1
;
with T as  -- tadm09a1 gruppieren und max PartitionSize berechnen
  ( SELECT  DB_NAME, TS_NAME, PARTITIONS_NR,
            sum(float(HI_U_RBA)) / 1024 / 1024 / 1024 USED,
            CASE      -- negative paLim bei GruppierungsFehlern
                 WHEN MIN(PARTITIONS_TOTAL) <> Max(PARTITIONS_TOTAL)
                     THEN -91
                 WHEN MIN(DS_SIZE) <> Max(DS_SIZE) THEN -92
                 WHEN MIN(LARGE) <> Max(LARGE) THEN -93
                      -- maximale PartitionSize in GB
                 WHEN MIN(PARTITIONS_TOTAL) = 0 THEN 64
                 WHEN MIN(DS_SIZE) <> 0 THEN INT(MIN(DS_SIZE)/1024/1024)
                 WHEN MIN(LARGE) = 'K' OR MIN(LARGE) = 'L' THEN 4
                 WHEN MIN(PARTITIONS_TOTAL) <=  16 THEN 4
                 WHEN MIN(PARTITIONS_TOTAL) <=  32 THEN 2
                 WHEN MIN(PARTITIONS_TOTAL) <=  64 THEN 1
                 WHEN MIN(PARTITIONS_TOTAL)  <= 254 THEN 4
                      -- > 254 parts hängt von pageSize ab --> Fehler
                 ELSE                              -94
            END paLim,
            MIN(PARTITIONS_TOTAL) partitions_total,
            min(DS_SIZE) ds_size,
            min(LARGE) large,
            DATUM DATUM
        from oa1a.TADM09A1
        group by  DB_NAME, TS_NAME, PARTITIONS_NR, DATUM
  ) ,
L as -- SchwellWerte tadm10a1 mit like Wert ergänzen
  ( select W.*,
           case when posStr(db_name, '%') < 1 then '% no %'
                else left(db_name, posStr(db_name, '%') - 1)
           end dbLike,
           case when posStr(ts_name, '%') < 1 then '% no %'
                else left(ts_name, posStr(ts_name, '%') - 1)
           end tsLike
        from oa1a.tadm10a1 W
        where w.END_DATUM >= timestamp(current date,'00:00:00')
  ) ,
S as        -- join R mit einem SchwellWert-Tupel aus TADM10A1,
            --     Tupel wird mit folgender Priorität gewählt
            --     1. db =,    ts =        , pa = or 0
            --     2. db =,    ts like     , pa = or 0
            --     3. db like, ts like or =, pa = or 0
            --     4. db DEFAULT
            --     5. default 90% der Limite
            -- like Operator geht hier nicht, wir vergleichen
            --     bis zum ersten %
  ( SELECT T.DB_NAME, T.TS_NAME, T.PARTITIONS_NR, T.used,
        -- Werte aus erster gefunden Schwellwert Row auswählen
        coalesce(spez.exclude, sTSl.exclude, sDBl.exclude,
                    sdef.exclude, 'N') exclude,
        coalesce(strip(spez.db_name) || '.' || strip(spez.ts_name)
                    || '.' || strip(char(spez.partitions_nr)),
                 strip(sTSl.db_name) || '.' || strip(sTSl.ts_name)
                    || '.' || strip(char(sTSl.partitions_nr)),
                 strip(sDBl.db_name) || '.' || strip(sDBl.ts_name)
                    || '.' || strip(char(sDBl.partitions_nr)),
                 strip(sDef.db_name) || '.' || strip(sDef.ts_name)
                    || '.' || strip(char(sDef.partitions_nr)),
                 '%default 90%') swKey,
        coalesce (
        case T.paLim     -- richtigen Schwellwert für paLim wählen
            when 1 then coalesce(spez.HIGHWATER_1GB,
                    sTSl.HIGHWATER_1GB , sDBl.HIGHWATER_1GB,
                    sDef.HIGHWATER_1GB)
            when 2 then coalesce(spez.HIGHWATER_2GB,
                    sTSl.HIGHWATER_2GB , sDBl.HIGHWATER_2GB,
                    sDef.HIGHWATER_2GB)
            when 4 then coalesce(spez.HIGHWATER_4GB,
                    sTSl.HIGHWATER_4GB , sDBl.HIGHWATER_4GB,
                    sDef.HIGHWATER_4GB)
            when 8 then coalesce(spez.HIGHWATER_8GB,
                    sTSl.HIGHWATER_8GB , sDBl.HIGHWATER_8GB,
                    sDef.HIGHWATER_8GB)
            when 16 then coalesce(spez.HIGHWATER_16GB,
                    sTSl.HIGHWATER_16GB , sDBl.HIGHWATER_16GB,
                    sDef.HIGHWATER_16GB)
            when 32 then coalesce(spez.HIGHWATER_32GB,
                    sTSl.HIGHWATER_32GB , sDBl.HIGHWATER_32GB,
                    sDef.HIGHWATER_32GB)
            when 64 then coalesce(spez.HIGHWATER_64GB,
                    sTSl.HIGHWATER_64GB , sDBl.HIGHWATER_64GB,
                    sDef.HIGHWATER_64GB)
            else    min(-89, T.paLim)
        end , 0.9 * T.paLim) sw,
        T.paLim, T.partitions_total, T.ds_size, T.large, T.datum
      FROM T
        left JOIN L SPEZ    -- Schwelle für db, ts und part%
          ON      SPEZ.DB_NAME       =    T.DB_NAME
              AND SPEZ.TS_NAME      =    T.TS_NAME
              AND SPEZ.PARTITIONS_NR IN (0 , T.PARTITIONS_NR)
        left JOIN L sTSl     -- Schwelle für db, ts% und part%
          ON      sTSl.DB_NAME       =    T.DB_NAME
              AND sTSl.tsLike  = left(T.ts_name, length(sTSl.tsLike))
              AND sTSl.PARTITIONS_NR IN (0 , T.PARTITIONS_NR)
        left JOIN l sDBl     -- Schwelle für db, ts% und part%
          ON      sDBl.dbLike  = left(T.db_name, length(sDBl.dbLike))
              AND ( sDBl.tsLike  = left(T.ts_name, length(sDBl.tsLike))
                    or sDBl.ts_name = T.ts_name )
              AND sDBl.PARTITIONS_NR IN (0 , T.PARTITIONS_NR)
        LEFT JOIN L  SDEF     -- Schwell Default
          ON SDEF.DB_NAME       =    'DEFAULT'
 )
--\*********************************************************************
--\
--\      Tablespace (Partitionen) grösser SchwellWert
--\
SELECT substr(DB_NAME,1,8) "db",
       substr(TS_NAME,1,8) "ts",
       char(case
           when partitions_nr <= 999 and partitions_total <= 999
               then right('  ' || strip(char(PARTITIONS_nr)), 3) || '/'
                    || right('  ' || strip(char(PARTITIONS_total)), 3)
               else strip(char(PARTITIONS_nr)) || '/'
           end, 7) "par/tot" ,
       dec(used, 4, 2) "used",
       dec(sw,   4, 2) "schWe",
       dec(paLim, 2, 0) "lim",
       char(swKey, 20)     "schwellWertKey"
    from S
    where datum = current date
        and exclude in ('N', 'S') and used > sw
    ORDER BY 1, 2, 3
;
--/
--/ db        = Datenbank
--/ ts        = Tablespace
--/ par/tot   = betroffene PartitionsNummer
--/             / Total Anzahl Partitionen des Tablespace
--/ used      = benutzter Speicherplatz in GB
--/ schWe     = Schwellwert in GB
--/ lim       = Limite in GB
--/ schwellWertKey = Key des Schwellwerts im Format db.ts.par
--/
--/*********************************************************************
with ts as   -- tablespace mit dsSz
  ( select s.*,
            case when partitions = 0 then 64 * 1024 * 1024
                 when dssize <> 0 then dssize
                 when type in ('K', 'L') then 4 * 1024 * 1024
                 when partitions <=  16 then 4 * 1024 * 1024
                 when partitions <=  32 then 2 * 1024 * 1024
                 when partitions <=  64 then 1 * 1024 * 1024
                 when partitions <= 254 then 4 * 1024 * 1024
                 when partitions <=  16 then 4 * 1024 * 1024
            end dsSz
        from sysibm.sysTablespace s
  ) ,
ii as   -- index mit pieceSz, pieceCnt und maxPartition
  (
    select i.*, t.tsName, p.maxPart,
        case when maxPart > 0 then 1
             when s.dsSize < 4e6 and not s.type in ('L', 'K') then 32
             else 4096
        end pieceCnt,
        case when maxPart > 0 then dsSz
             when pieceSize > 0 then piecesize
             when s.dsSz >= 4 then 4 * 1024 * 1024
             else 2  * 1024 * 1024
        end pieceSz
    from sysibm.sysindexes i, sysibm.systables t, ts s,
        ( select max(partition) maxPart, ixCreator, ixName
               from sysibm.sysindexpart p
               group by ixCreator, ixName
        ) p
    where
            i.tbCreator = t.creator and i.tbName = t.name
        and t.dbName = s.dbName and t.tsName = s.name
        and i.creator = p.ixCreator and i.name = p.ixName
  ) ,
L as --* SchwellWerte tadm10a1 mit like Wert ergänzen
  ( select W.*,
           case when posStr(db_name, '%') < 1 then '% no %'
                else left(db_name, posStr(db_name, '%') - 1)
           end dbLike,
           case when posStr(ts_name, '%') < 1 then '% no %'
                else left(ts_name, posStr(ts_name, '%') - 1)
           end tsLike
        from oa1a.tadm10a1 W
        where w.END_DATUM >= timestamp(current date,'00:00:00')
  ),
RR as --* RTS mit Limite und Schwellwert
  (
  select r.*,
       ii.creator ixCreator, ii.name ixName, ii.maxPart,
       ii.tbCreator, ii.tbName, ii.tsName,
       float(r.nActive) * 4 / 1024 / 1024 activeGB,
       float(r.space)       / 1024 / 1024 spaceGB,
       ii.pieceCnt limitPieces,
       float(ii.pieceSz) * ii.pieceCnt / 1024 / 1024 limitGB,
       coalesce(L1.HIGHWATER_1GB, L2.HIGHWATER_1GB, L3.HIGHWATER_1GB,
                L4.HIGHWATER_1GB, .8)  swFrc,
       coalesce(L1.exclude, L2.exclude, L3.exclude,
                    l4.exclude, 'N') exclude,
       coalesce(strip(l1.db_name) || '.' || strip(l1.ts_name)
                    || ':' || strip(char(l1.partitions_nr)),
                strip(l2.db_name) || '.' || strip(l2.ts_name)
                    || ':' || strip(char(l2.partitions_nr)),
                strip(l3.db_name) || '.' || strip(l3.ts_name)
                    || ':' || strip(char(l3.partitions_nr)),
                strip(l4.db_name) || '.' || strip(l4.ts_name)
                    || ':' || strip(char(l4.partitions_nr)),
                'sql default') swKey
      from sysibm.sysindexspacestats r
        left join ii on ii.dbid = r.dbid and ii.isobid = r.isobid
        left JOIN L L1      --* Schwelle für db, ts und part%
          ON      L1.DB_NAME       =    ii.DBNAME
              AND L1.TS_NAME      =    ii.indexSpace
              AND L1.PARTITIONS_NR IN (0 , r.PARTITION)
        left JOIN L L2       --* Schwelle für db, ts% und part%
          ON      L2.DB_NAME       =   ii.DBNAME
              AND L2.tsLike  = left(ii.indexSpace,length(L2.tsLike))
              AND L2.PARTITIONS_NR IN (0 , r.PARTITION)
        left JOIN l L3       --* Schwelle für db, ts% und part%
          ON      L3.dbLike  = left(ii.dbname, length(L3.dbLike))
              AND ( L3.tsLike  = left(ii.indexspace, length(L3.tsLike))
                    or L3.ts_name = ii.indexSpace )
              AND L3.PARTITIONS_NR IN (0 , r.PARTITION)
        LEFT JOIN L L4        --* Schwell Default
          ON L4.DB_NAME       =    'DEFAULT/I'
  )
--\*********************************************************************
--\
--\      IndexSpace (Partitionen) grösser SchwellWert * Limite
--\
SELECT substr(DBNAME,1,8) "db",
       substr(indexSpace,1,8) "indexSpc",
       char(case
           when partition <= 999 and maxPart <= 999
               then right('  ' || strip(char(PARTITION)), 3) || '/'
                    || right('  ' || strip(char(maxPart)), 3)
               else strip(char(PARTITION)) || '/'
           end, 7) "par/tot" ,
       char(
       right('     '||strip(cast(dec(activeGB, 8, 3) as char(10))),10)
       || char(dec(swFrc, 3, 2))
       || right('     '||strip(cast(dec(limitGB, 8,3) as char(10))),10)
           , 25)        "    active scWe     limit",
       char(left(ixName, 20), 20)  "index name"
    from RR
    where exclude in ('N', 'S') and activeGB > swFrc * limitGB
    ORDER BY 1, 2, 3
    ;
--/
--/ db        = Datenbank
--/ indexSp   = index Space (Nicht Name|)
--/ par/tot   = betroffene PartitionsNummer / Total Partitonen
--/ active    = Speicherplatz in GB der active Pages
--/ schWe     = Schwellwert Faktor
--/ lim       = Limite in GB
--/ indexName = Name des Index
--/
--/*********************************************************************
--$SPECIAL
select current timestamp "timestamp",
       current member "member", current server "server",
               '11.9.13 neue queries' "version"
    from sysibm.sysDummy1
;
with t0 as
(
  select dbname db, name ts, pgSize
      , partitions parts, maxPartitions maxParts, dsSize
      , case
            when type <> ' ' then type
            when partitions > 0 and segsize = 0 then 'p' -- classic part
            when partitions = 0 and segsize = 0 then 'i' -- simple
            when partitions = 0 and segsize > 0 then 's' -- segmented
            else raise_error(70000, 'unknown ts type='||type
                || ' partitions=' || strip(char(partitions))
                || ' segsize=' || strip(char(segsize))
                || ' db.ts=' || strip(dbName) ||'.'||name) end tsTy
      , case
            when dssize <> 0 then int(dssize / 1048576)
            when type in ('G', 'O', 'P', 'R', 'L') then 4
            when partitions = 0     then  64
            when partitions > 254 then    pgSize
            when partitions > 64    then   4
            when partitions > 32    then   1
            when partitions > 16    then   2
                                    else   4
        end dsGB
      , dbid, psid
      from sysibm.sysTablespace
)
, ts as
( select t0.*
      , case when tsTy = 'G' or parts = 0 then 0 else 9999 end scope
      , case when tsTy = 'G' then dsGB * maxparts
             when tsTy = 'O' then dsGB * 254
             else dsGb end limGB
      from t0
)
, tk1 as
(
  select ts.*
      , value( ( select max(a.key)
        from s100447.tGbGrSchwelle
          for business_time as of current date a
        where a.part = 0
          and left(a.db, a.dbLen) = left(ts.db, a.dbLen)
          and left(a.ts, a.tsLen) = left(ts.ts, a.tsLen)
          and (a.tsTy = ' ' or a.tsTy = ts.tsTy)
          and a.dsMin <= ts.limGB
          ), raise_error(70001, 'schwelle null ' || db ||'.'||ts
                      || ' ty='||tsTy)
      ) keyTS
    from ts
)
, tr as
(
  select tk1.*
      , min(partition, scope) part
      , nActive nAct
    from tk1 join sysibm.sysTableSpaceStats r
      on tk1.db = r.dbName and tk1.ts = r.name
         and tk1.dbid = r.dbid and tk1.psid = r.psid
)
, tg (db, ts, part, limGb, keyTS, nAct
     , pgSize, parts, maxParts, dsSize, tsTy, dsGB) as
(
  select db, ts, part, min(limGb), max(keyTS), sum(bigInt(nAct))
      , max(pgSize), max(parts), max(maxParts), max(dsSize)
      , max(tsTy), max(dsGB)
    from tr
    group by db, ts, part
)
, i1 as
(
  select i.indexType, i.pieceSize, i.creator ixCr, i.name ix
         , case when i.pgSize = 4096 or i.compress = 'Y' then 4
                else i.pgSize
           end ixPgSz
         , (select max(partition)
              from sysibm.sysIndexPart p
                  where p.ixCreator = i.creator
                    and p.ixName = i.name
           ) ixPaMax
         , tk1.*
    from tk1
      join sysibm.sysTables t
        on tk1.db = t.dbName and tk1.ts = t.tsName
            and t.type not in ('A', 'V')
      join sysibm.sysIndexes i
        on i.tbCreator = t.creator and i.tbName = t.name
)

, i2 as
(
  select case when piecesize <> 0 then real(pieceSize) / 1048576
              when parts <> 0 then real(dsGB) * ixPgSz / pgSize
              else 2
         end pcGb
       , i1.*
      from i1
)
,  i3 as
(
  select case when ixPaMax <> 0 then 1
              when parts = 0 then 32
              when tsTy <> 'L' and dsSize = 0 and parts <= 64 then 32
              when parts > 254 then 4096
              else smallInt(min(4096, 4096 / pcGb * ixPgSz))
         end pcMx
         , i2.*
      from i2
)
,  iR as
(
  select pcGb * pcMx ixpGb
       , float(r.nActive) * i3.ixPgSz / 1048576 actGB
       , r.partition part
       , i3.*
    from i3 left join sysibm.sysindexspacestats r
      on i3.ixCr = r.creator and i3.ix = r.name
)
, u1 (db, ts, ix, part, parts, limGb, actGb, tsTy, keyTs) as
(
  select           db, ts, ' --ts--', part, parts, limGb
          , float(nAct) * pgSize / 1048576
          , tsTy, keyTS
    from tg
  union all select db, ts, ix, part, ixPaMax, ixpGb, actGb, tsTy, keyTS
    from iR
)
, uK  as
(
  select u1.*
      , case when u1.part is null or u1.part < 1 then keyTS
             else value ( ( select max(a.key)
        from s100447.tGbGrSchwelle
          for business_time as of current date a
        where u1.part > 0 and a.part = u1.part and a.key > u1.keyTS
          and left(a.db, a.dbLen) = left(u1.db, a.dbLen)
          and left(a.ts, a.tsLen) = left(u1.ts, a.tsLen)
          and (a.tsTy = ' ' or a.tsTy = u1.tsTy)
          and a.dsMin <= u1.limGB
          ), u1.keyTS) end key
    from u1
)
, uS as
(
  select j.schwelle
      , smallint(round(actGb * 100 / limGB, 0)) used
      , uK.*
    from uK
      join s100447.tGbGrSchwelle
          for business_time as of current date j
        on uK.key = j.key
)
--\*********************************************************************
--\
--\      Tablespace und Index Partitionen grösser SchwellWert
--\
select substr(db, 1, 8) "db"
     , substr(ts, 1, 8) "ts"
     , substr(case when part = 0 then ''
              else value(right('   '||strip(char(part)), 4), '----')
             ||'/'|| value(right('   '||strip(char(parts)), 4), '----')
        end, 1, 9) "part/ tot"
     , substr(ix, max(1, length(ix) - 7), 8) "...index"
     , dec(limGb, 6, 0) "lim GB"
     , dec(schwelle, 3, 0) "schw%"
     , dec(used, 3, 0) "used%"
     , tsTy "y"
    from oa1p.vAdm13GbGr g
    where used > schwelle
    order by g.db, g.ts, g.part, g.ix
;
--/
--/ db        = Datenbank
--/ ts        = tablespace
--/ part/ tot = betroffene PartitionsNummer / Total Partitonen
--/ index     = index oder --ts--
--/ lim GB    = physische Limite in GB
--/ schw%     = Schwellwert in Prozent der Limite
--/ used%     = benutzter Plat in Prozent der Limite
--/ y         = tsType s=Segmented,i=Simple p=Partitioned classic
--/             andere Werte aus sysibm.sysTableSpace.type
--/ key ...   = key des Schwellwerts aus S100447.tGbGrSchwelle
--/             abgeschnitten siehe DSN.jobname.MAIL1
--/*********************************************************************
--$SPECIAL
select current timestamp "timestamp",
       current member "member", current server "server",
               '11.9.13 ende' "version"
    from sysibm.sysDummy1
;