zOs/SQL/REOIX

set current path oa1t;
select
        substr(strip(db) ||'.' || strip(ts), 1, 17) "db.ts",
        substr(ix, 1, 12) "index",
        smallint(part) "part",
        substr(fosFmTime(reorgTime), 1, 5) "reoTi",
        importance "imp",
        reason "reason",
        s.*
    from s100447.VReoIx s
    where 1=1
        and db like 'WF%'
     -- and TS like 'APER24%'
     -- and importance > 0
    order by db, ts, ix, part
    with ur
;x;
select *
      from s100447.tReoIXParms e
;
with sw as
( select
          CASE WHEN POSSTR(DB,  '*') > 0
               THEN POSSTR(DB,  '*') - 1 ELSE 8 END DBLEN,
          CASE WHEN POSSTR(TS,  '*') > 0
               THEN POSSTR(TS,  '*') - 1 ELSE 8 END TSLEN,
          CASE WHEN POSSTR(IX,  '*') > 0
               THEN POSSTR(IX,  '*') - 1 ELSE 20 END IXLEN,
          substr(right('00' || STRIP(CHAR(PRIO)), 2), 1, 2) prC2,
          e.*
      from s100447.tReoIXParms e
)
select * from sw
;
-- create view S100447.vReoIXSchwelle as
with sw as
( select
          CASE WHEN POSSTR(DB,  '*') > 0
               THEN POSSTR(DB,  '*') - 1 ELSE 8 END DBLEN,
          CASE WHEN POSSTR(TS,  '*') > 0
               THEN POSSTR(TS,  '*') - 1 ELSE 8 END TSLEN,
          CASE WHEN POSSTR(IX,  '*') > 0
               THEN POSSTR(IX,  '*') - 1 ELSE 20 END IXLEN,
          substr(right('00' || STRIP(CHAR(PRIO)), 2), 1, 2) prC2,
          e.*
      from s100447.tReoIXParms e
)
select i.creator cr, i.name ix, p.partition part,
           substr(max(prC2 || char(sw.reorg      )), 3)   swReorg     ,
       int(substr(max(prC2 || char(pageSplits )), 3)) swPageSplits,
       int(substr(max(prC2 || char(sw.EXTENTS  )), 3)) swEXTENTS    ,
       int(substr(max(prC2 || char(REORGDAYS  )), 3)) swREORGDAYS ,
       int(substr(max(prC2 || char(INSERTS    )), 3)) swINSERTS    ,
       int(substr(max(prC2 || char(DELETES    )), 3)) swDELETES    ,
       int(substr(max(prC2 || char(pseudoDel  )), 3)) swPseudoDel ,
       min(i.dbName) db, min(i.indexSpace) is, min(t.tsName) ts,
       min(i.dbId) dbId, min(i.isoBid) isoBid,
       min(p.createdTS) createdTS,
       min(t.creator) tbCr, min(t.name) tb
    from
        SYSIBM.sysIndexes           I
        join SYSIBM.SYSTABLES       T
            on i.tbCreator = t.creator and i.tbName = t.name
               and i.dbName = t.dbName
        join SYSIBM.SYSIndexPart    p
            on p.ixCreator = i.creator and p.ixName = i.name
        , sw
    where   left(i.dbName, dbLen) = left(db, dbLen)
        and left(i.name, ixLen) = left(ix, ixLen)
        and left(t.tsName, tsLen) = left(ts, tsLen)
        and p.partition between partVon and partBis
        and current date between guVon and guBis
        and i.dbName like 'WF%'
    group by i.creator, i.name, p.partition
;x;
select '<' || char(STRIP(CHAR(1   )), 2)||'>' from sysibm.sysdummy1;X;
set current path = oA1t;
SELECT *
    from s100447.VReoIx s
    where db like 'WF%'
;x;
create view S100447.vReoIXSchwelle as
with sw as
( select
          CASE WHEN POSSTR(DB,  '*') > 0
               THEN POSSTR(DB,  '*') - 1 ELSE 8 END DBLEN,
          CASE WHEN POSSTR(TS,  '*') > 0
               THEN POSSTR(TS,  '*') - 1 ELSE 8 END TSLEN,
          CASE WHEN POSSTR(IX,  '*') > 0
               THEN POSSTR(IX,  '*') - 1 ELSE 20 END IXLEN,
          substr(right('00' || STRIP(CHAR(PRIO)), 2), 1, 2) prC2,
          e.*
      from s100447.tReoIXParms e
)
select i.creator cr, i.name ix, p.partition part,
           substr(max(prC2 || char(reorg      )), 3)   swReorg     ,
       int(substr(max(prC2 || char(pageSplits )), 3)) swPageSplits,
       int(substr(max(prC2 || char(sw.EXTENTS  )), 3)) swEXTENTS    ,
       int(substr(max(prC2 || char(REORGDAYS  )), 3)) swREORGDAYS ,
       int(substr(max(prC2 || char(INSERTS    )), 3)) swINSERTS    ,
       int(substr(max(prC2 || char(DELETES    )), 3)) swDELETES    ,
       int(substr(max(prC2 || char(pseudoDel  )), 3)) swPseudoDel ,
       min(i.dbName) db, min(i.indexSpace) is, min(t.tsName) ts,
       min(i.dbId) dbId, min(i.isoBid) isoBid,
       min(p.createdTS) createdTS,
       min(t.creator) tbCr, min(t.name) tb
    from
        SYSIBM.sysIndexes           I
        join SYSIBM.SYSTABLES       T
            on i.tbCreator = t.creator and i.tbName = t.name
               and i.dbName = t.dbName
        join SYSIBM.SYSIndexPart    p
            on p.ixCreator = i.creator and p.ixName = i.name
        , sw
    where   left(i.dbName, dbLen) = left(db, dbLen)
        and left(i.name, ixLen) = left(ix, ixLen)
        and left(t.tsName, tsLen) = left(ts, tsLen)
        and p.partition between partVon and partBis
        and current date between guVon and guBis
    group by i.creator, i.name, p.partition
;
???????????????????????
------------------------------------------------------------------------
-- RTS-Stats Werte pro ix-Partition zu Schwellen joinen
--     Kolonnen Namen: sw*: Schwellen
--
create view S100447.vReoIxStats as
  select cr, ix, part, db, is, ts, tbCr, tb, createdTS,
         swReorg     , swPageSplits, swEXTENTS   , swREORGDAYS ,
         swINSERTS   , swDELETES   , swPseudoDel ,
         max(CAST(TOTALEntries AS REAL), 100) rEntrs,
         cast(nActive AS REAL) rActive,
         max(coalesce(reorgLastTime,   createdTS),
             coalesce(loadrLastTime,   createdTS),
             coalesce(rebuildLastTime, createdTS)) lastBuilt ,
         coalesce(real(max(r.space, 0)) * 1024 * 1.3558420E-07 , 0)
             + 1.8626988 reorgTime ,
         r.*
    from S100447.vReoIXSchwelle s
        left join sysibm.sysIndexSpaceStats r
        on      r.DBID          = S.DBID
            AND r.ISOBID        = S.ISOBID
            AND r.DBNAME        = S.DB
            AND r.indexSpace    = S.is
            AND r.partition     = s.part
;
------------------------------------------------------------------------
-- vReoIx: SchwellwertUeberschreitungen herausfinden
--            in riesigem case statement
--
create view S100447.vReoIX as
with ix1 as
(
  select s.*
    , value(
        ( select 'no - db status ' || strip(d.sta)
            from s100447.tDbState d
            where d.sta like 'STOP%'
              and d.Ty = 'D' and d.db = s.db
            fetch first row only
        )
      , ( select 'no - ts status ' || strip(t.sta)
            from s100447.tDbState t
            where t.sta like 'STOP%'
              and t.Ty            = 'T'
              and t.db            = s.db
              AND t.sp            = s.ts
              AND t.paFr         <= s.part
              AND t.paTo         >= s.part
            fetch first row only
        )
      , ( select substr(min(
               case when i.sta like 'RO%' or i.sta like 'STOP%'
                                          or i.sta like '%RBD%'
                        then '1no - ix status ' || strip(i.sta)
                    when ',' || strip(i.sta) || ',' like '%,REORP,%'
                        then '2pending reorp ' || strip(i.sta)
                    when ',' || strip(i.sta) || ',' like '%,AREOR,%'
                        then '3pending areor ' || strip(i.sta)
                    else null end), 2)
            from s100447.tDbState i
            where   i.Ty            = 'I'
                and i.db            = s.db
                AND i.sp            = s.is
                and ( i.paFr = 0 or s.part = 0
                 or (   i.paFr <= s.part
                    AND i.paTo >= s.part ))
      ) ) xSta
    from S100447.vReoIXStats s
)
, ix2 as
( select
    case
        when swReorg = 'NEVER' then 'no - reorgNever'
        when xSta is not null then xSta
        when swReorg = 'ALWAYS' then 'reorgAlways'
        when indexSpace is null then 'rtsMissing'
        when REORGLASTTIME IS NULL and LOADRLASTTIME IS NULL
                  and REBUILDLASTTIME IS NULL then 'rtsNull'
        when rEntrs is null then 'rtsRowsNull'
        when totalEntries < 0 then 'rtsEntries '
                  || strip(char(totalEntries)) || ' < 0'
        when REORGLEAFFAR > rActive / 100 * swPageSplits
            then 'pageSplits ' || strip(char(reorgLeafFar)) || ' > '
                || strip(char(swPageSplits))
                || '% of ' || strip(char(nActive))
        when extents         > swExtents
            then 'extents ' || strip(char(extents)) || ' > '
                || strip(char(swExtents))
        when reorgInserts    > rEntrs / 100 * swInserts
            then 'inserts ' || strip(char(reorgInserts)) || ' > '
                || strip(char(swInserts)) || '% of '
                || strip(char(totalEntries))
        when reorgDeletes    > rEntrs / 100 * swDeletes
            then 'deletes ' || strip(char(reorgDeletes)) || ' > '
                || strip(char(swDeletes)) || '% of '
                || strip(char(totalEntries))
        when reorgPseudoDeletes    > rEntrs / 100 * swPseudoDel
            then 'pseudoDel ' || strip(char(reorgPseudoDeletes))||' > '
                || strip(char(swPseudoDel)) || '% of '
                || strip(char(totalEntries))
        when CURRENT TIMESTAMP - swReorgDays days > lastBuilt
            then 'lastBuilt ' || char(date(lastBuilt)) || ' older '
                || strip(char(swReorgDays)) ||' reorgDays'
        else 'no - reorg not required'
    end reason, s.*
    from ix1 s
)
    -- importance voranstellen
select smallint(case
            when reason = 'no - reorg not required' then  0
            when reason like 'no %'                 then -1
            when reason like 'lastBuilt %'          then  3
            when reason like 'pending areo*%'       then  7
            when reason like 'pending %'            then 11
            when reason like 'reorgAlway%'          then  9
                                                    else  5
          end) importance,
       ix2.*
    from ix2
;
------------------------------------------------------------------------
-- vReoJobParms: jobLen und prC2 anfügen
--
CREATE VIEW S100447.vReoJobParms AS
      SELECT e.*,
          CASE WHEN POSSTR(job, '*') > 0
               THEN POSSTR(job, '*') - 1 ELSE 8 END jobLEN,
          substr(right('00' || STRIP(CHAR(PRIO)), 2), 1, 2) prC2
      FROM s100447.TReoJobParms e
;
CREATE VIEW S100447.vReoRunTsStats    AS
with tp as
( select
          real(totalRows)                           rows
       ,  log10(max(real(totalRows),1))             logRows
       ,  real(space) * 1024                        spc
       ,  log10(max(real(space), 1)*1024)           logSpc
       ,  real(uncompressedDatasize)                uds
       ,  log10(max(real(uncompressedDatasize), 1)) logUds
       ,  r.*
      from s100447.tReoRunTsStats r
)
, t as
( select tst, rng
       , min(partition)            partMin
       , max(partition)            partMax
       , count(*)                  parts
       , sum(rows)                 rows
       , max(rows)                 rowsMax
       , sum(rows * logrows)       rowsLog
       , sum(rows) * max(logRows)  rowsLogMax
       , sum(spc)                  spc
       , sum(spc * logSpc)         spcLog
       , sum(spc * logRows)        spcLogRows
       , max(spc)                  spcMax
       , sum(spc) * max(logSpc)    spcLogMax
       , sum(Uds)                  Uds
       , sum(Uds * logUds)         UdsLog
       , sum(Uds * logRows)        UdsLogRows
       , max(Uds)                  UdsMax
       , sum(Uds) * max(logUds)    UdsLogMax
      from tp
      group by tst, rng
)
,    ip as
( select
          real(totalEntries) ent,
          log10(max(real(totalEntries),1)) logEnt,
          real(space) * 1024 spc,
          log10(max(real(space), 1)*1024) logSpc,
          r.*
      from s100447.tReoRunIxStats r
)
,    i as
( select tst, rng, count(*)        parts
       , sum(ent)                  ent
       , max(ent)                  entMax
       , sum(ent * logEnt)         entLog
       , sum(ent) * max(logEnt)    entLogMax
       , sum(spc)                  spc
       , sum(spc * logSpc)         spcLog
       , sum(spc * logEnt)         spcLogEnt
       , max(spc)                  spcMax
       , sum(spc) * max(logSpc)    spcLogMax
      from ip
      group by tst, rng
)
select j.job, r.*
       , partMin                      tsPartMin
       , partMax                      tsPartMax
       , value(t .parts          , 0) tsParts
       , value(t .rows           , 0) tsRows
       , value(t .rowsMax        , 0) tsRowsMax
       , value(t .rowsLog        , 0) tsRowsLog
       , value(t .rowsLogMax     , 0) tsRowsLogMax
       , value(t .spc            , 0) tsSpc
       , value(t .spcLog         , 0) tsSpcLog
       , value(t .spcLogRows     , 0) tsSpcLogRows
       , value(t .spcMax         , 0) tsSpcMax
       , value(t .spcLogMax      , 0) tsSpcLogMax
       , value(t .Uds            , 0) tsUds
       , value(t .UdsLog         , 0) tsUdsLog
       , value(t .UdsLogRows     , 0) tsUdsLogRows
       , value(t .UdsMax         , 0) tsUdsMax
       , value(t .UdsLogMax      , 0) tsUdsLogMax
       , value(ix.parts          , 0) ixparts
       , value(ix.ent            , 0) ixent
       , value(ix.entMax         , 0) ixentMax
       , value(ix.entLog         , 0) ixentLog
       , value(ix.entLogMax      , 0) ixentLogMax
       , value(ix.spc            , 0) ixspc
       , value(ix.spcLog         , 0) ixspcLog
       , value(ix.spcLogEnt      , 0) ixspcLogEnt
       , value(ix.spcMax         , 0) ixspcMax
       , value(ix.spcLogMax      , 0) ixspcLogMax
       , value(i0.parts          , 0) i0parts
       , value(i0.ent            , 0) i0ent
       , value(i0.entMax         , 0) i0entMax
       , value(i0.entLog         , 0) i0entLog
       , value(i0.entLogMax      , 0) i0entLogMax
       , value(i0.spc            , 0) i0spc
       , value(i0.spcLog         , 0) i0spcLog
       , value(i0.spcLogEnt      , 0) i0spcLogEnt
       , value(i0.spcMax         , 0) i0spcMax
       , value(i0.spcLogMax      , 0) i0spcLogMax
    from s100447.tReoRunJob j, s100447.tReoRunPart r
        left join t on t.tst = r.tst and t.rng = r.rng
        left join i ix on ix.tst = r.tst and ix.rng = r.rng
        left join i i0 on i0.tst = r.tst and i0.rng = r.rngI0
                                       and r.rngI0 > 0
    where j.ty = 'TS' and j.sta <> '0' and r.ty = 't' and r.sta = 'r'
        and r.part = r.pavon and r.reoTime is not null
        and r.tst = j.tst
;
CREATE VIEW S100447.vReoRunIxStats    AS
with ip as
( select
          real(totalEntries) ent,
          log10(max(1, real(totalEntries))) logEnt,
          real(space) * 1024 spc,
          log10(max(1, real(space)*1024)) logSpc,
          r.*
      from s100447.tReoRunIxStats r
)
,    i as
( select tst, rng, count(*)        parts
       , min(partition)            partMin
       , max(partition)            partMax
       , sum(ent)                  ent
       , max(ent)                  entMax
       , sum(ent * logEnt)         entLog
       , sum(ent) * max(logEnt)    entLogMax
       , sum(spc)                  spc
       , sum(spc * logSpc)         spcLog
       , sum(spc * logEnt)         spcLogEnt
       , max(spc)                  spcMax
       , sum(spc) * max(logSpc)    spcLogMax
      from ip
      group by tst, rng
)
select j.job, r.*
       , partMin                      partMin
       , partMax                      partMax
       , value(ix.parts          , 0) parts
       , value(ix.ent            , 0) ent
       , value(ix.entMax         , 0) entMax
       , value(ix.entLog         , 0) entLog
       , value(ix.entLogMax      , 0) entLogMax
       , value(ix.spc            , 0) spc
       , value(ix.spcLog         , 0) spcLog
       , value(ix.spcLogEnt      , 0) spcLogEnt
       , value(ix.spcMax         , 0) spcMax
       , value(ix.spcLogMax      , 0) spcLogMax
    from s100447.tReoRunJob j, s100447.tReoRunPart r
        left join i ix on ix.tst = r.tst and ix.rng = r.rng
    where j.ty = 'IX' and j.sta <> '0' and r.ty = 'i' and r.sta = 'r'
        and r.part = r.pavon and r.reoTime is not null
        and r.tst = j.tst
;
create view S100447.vReoTSStatsPlus as
select r.*, s.pgSize, p.pageSave,
        case when r.uncompressedDatasize > 0
                 and real(r.nActive) * s.pgSize * 102400
                       / min(max(100-p.pageSave, 3), 100)
                 between real(r.uncompressedDatasize) / 7
                     and real(r.uncompressedDatasize) * 7
             then bigInt(r.uncompressedDatasize)
             else
                  bigInt(real(r.nActive) * s.pgSize * 102400
                       / min(max(100-p.pageSave, 3), 100))
        end fixUncomp
    from sysibm.sysTableSpaceStats r,
         sysibm.sysTableSpace s, sysibm.sysTablePart p
    where   s.dbName = r.dbName and s.name = r.name
        and s.dbid = r.dbId and s.psid = r.psid
        and p.dbName = r.dbName and p.tsName = r.name
        and p.partition = r.partition
;
create view S100447.vReoTSStatsFix    as
    select UPDATESTATSTIME
         , NACTIVE
         , NPAGES
         , EXTENTS
         , LOADRLASTTIME
         , REORGLASTTIME
         , REORGINSERTS
         , REORGDELETES
         , REORGUPDATES
         , REORGUNCLUSTINS
         , REORGDISORGLOB
         , REORGMASSDELETE
         , REORGNEARINDREF
         , REORGFARINDREF
         , STATSLASTTIME
         , STATSINSERTS
         , STATSDELETES
         , STATSUPDATES
         , STATSMASSDELETE
         , COPYLASTTIME
         , COPYUPDATEDPAGES
         , COPYCHANGES
         , COPYUPDATELRSN
         , COPYUPDATETIME
         , IBMREQD
         , DBID
         , PSID
         , PARTITION
         , INSTANCE
         , SPACE
         , TOTALROWS
         , DATASIZE
         , fixUncomp UNCOMPRESSEDDATASIZE
         , DBNAME
         , NAME
$@[ if $db2v10ENF then $@=[
         , REORGCLUSTERSENS -- from here new db2v10 columns
         , REORGSCANACCESS
         , REORGHASHACCESS
         , HASHLASTUSED
         , DRIVETYPE
         , LPFACILITY
         , STATS01
 $] $]
    from S100447.vReoTSStatsPlus
;
-- check views ------------------------------------------------------
---------------------------------------------------------------------
-- test tReoRunJob (and tReoRunPart.reoTst)
-- message e not null ==> error message ==> see case statement below
-- eo2 = calculate better eoj
---------------------------------------------------------------------
create view s100447.vReoRunJobChk as
with p as -- part gruppiert nach job, nur ty='r'
(select tst, ty, count(*) cnt,
     count(reotst) cntReo,
     min(reoTst) reoTstVon,
     max(reoTst) reoTstBis
    from s100447.tReoRunPart
    where sta = 'r'
    group by tst, ty
), j as -- join to job
(
select j.*,
       p.ty pTy, p.cnt pCnt, p.cntReo,
       p.reoTstVon, p.reoTstBis,
       (select min(tst)
            from s100447.tReoRunJob a
            where a.job = j.job and a.tst > j.tst
       ) nextJob
    from s100447.tReoRunJob j
      left join p
        on j.tst = p.tst and p.ty = lower(left(j.ty, 1))
)
        ----> diese case statement macht error message <-------------
select  case when eoj is null and nextJob is not null
                 then 'null not last'
             when reoTstVon < tst then 'reoTst < tst'
             when reoTstBis > nextJob then 'reoTst > nextJob'
             when reoTstBis > eoj then 'reoTst > eoj'
             when eoj > nextJob then 'overlap nextJob'
             when reoTstBis - tst > 1000000 then 'reoTst > 1 day'
      --     when eoj - tst > 1000000 then 'eoj > 1 day'
             else null
        end e,
        case when pCnt is null or pCnt < 1 then tst
             when reoTstBis is not null
                  and (nextJob is null or nextJob > reoTstBis)
                  and (tst < current timestamp - 2 days
                        or pCnt = cntReo) then reoTstBis
             when nextJob is not null then
                  nextJob
             else null
        end eo2, j.*
    from j
;
---------------------------------------------------------------------
-- check tReoRunPart
-- message e not null ==> error message ==> see case statement below
-- newTime = calculate reoTime from current values
---------------------------------------------------------------------
create view S100447.vReoRunRngChk as
with r as -- part gruppiert nach range
(
select
    (select j.job from s100447.tReoRunJob j where j.tst = p.tst) job,
    p.tst, p.rng,
    min(ty) ty,
    count(distinct ty) cdTy,
    min(sta) sta,
    count(distinct sta) cdSta,
    sum(case when part = paVon then 1 else 0 end) cPaVon,
    sum(case when part = paBis then 1 else 0 end) cPaBis,
    count(*) cnt,
    count(distinct part) cdPart,
    count(reoTst) cReoTst,
    min(reoTst) minReoTst,
    max(reoTst) maxReoTst,
    (select max(b.reoTst) -- letzter reoTst aus vorgehenden Ranges
          from s100447.tReoRunPart b
          where b.tst = p.tst and b.rng < p.rng) befReoTst,
    (select min(sta) || max(sta) -- status und reoTst aus Range -1
            || case when count(*) = count(reotst) then '=' else '0' end
            || coalesce(char(max(reoTst)), '-')
          from s100447.tReoRunPart b
          where b.tst = p.tst and b.rng = p.rng-1) r1ReoTst,
    (select min(sta) || max(sta) -- status und reoTst aus Range -2
            || case when count(*) = count(reotst) then '=' else '0' end
            || coalesce(char(max(reoTst)), '-')
          from s100447.tReoRunPart b
          where b.tst = p.tst and b.rng = p.rng-2) r2ReoTst,
    max(case when part = paVon then reoTime else null end) reoTime
  from s100447.tReoRunPart p
  group by tst, rng
) , s as -- begTst aus range -1 und range -2 berechnen
( select r.*,
      case when rng = 1 then tst
           when left(r1ReoTst, 3) = 'rr='
               then timestamp(substr(r1ReoTst, 4))
           when left(r1ReoTst, 2) <> '00' then null
           when rng = 2 then tst
           when left(r2ReoTst, 3) = 'rr='
               then timestamp(substr(r2ReoTst, 4))
           else null
           end begTst
    from r
), t as -- aktuelle reoZeit berechnen
( select s.*,
        (days(maxReoTst) - days(begTst)) * 86400
        + midnight_seconds(maxReoTst) - midnight_seconds(begTst)
        + 1e-6 * (microsecond(maxReoTst)-microsecond(begTst)) newTime
    from s
)
select ---> case statement macht error message <--------------------
    case when job is null   then 'job missing'
         when cdTy <> 1     then 'ty not unique'
         when cdSta <> 1    then 'sta not unique'
         when cPaVon <> 1   then 'part=paVon not unique'
         when cPaBis <> 1   then 'part=paBis not unique'
         when cdPart <> cnt then 'part not distinct'
         when minReoTst < tst then 'reoTst < tst'
                           -- rng waren früher anders sortiert
         when tst < '2011-09-29-00.00.00'  then null
         when befReoTst > minReoTst then 'before ReoTst > minReoTst'
         when abs(reoTime-newTime) >= 1 then 'reoTime <> newTime'
         else null
    end e,
    t.*
    from t
;
commit
;
--- end of install v5.9 -------------------------------------
$/view/
$/ddl/